Skip to content

Commit

Permalink
Merge pull request #817 from minhqdao/resolve-config-file
Browse files Browse the repository at this point in the history
Add global config file, implement local and remote registry
  • Loading branch information
minhqdao authored Apr 7, 2023
2 parents ef6532b + e1eb03b commit 4ba0bf9
Show file tree
Hide file tree
Showing 27 changed files with 3,671 additions and 732 deletions.
14 changes: 7 additions & 7 deletions app/main.f90
Original file line number Diff line number Diff line change
Expand Up @@ -99,20 +99,20 @@ function has_manifest(dir)
has_manifest = exists(join_path(dir, "fpm.toml"))
end function has_manifest

subroutine handle_error(error)
type(error_t), optional, intent(in) :: error
if (present(error)) then
write(error_unit, '("[Error]", 1x, a)') error%message
subroutine handle_error(error_)
type(error_t), optional, intent(in) :: error_
if (present(error_)) then
write (error_unit, '("[Error]", 1x, a)') error_%message
stop 1
end if
end subroutine handle_error

!> Save access to working directory in settings, in case setting have not been allocated
subroutine get_working_dir(settings, working_dir)
subroutine get_working_dir(settings, working_dir_)
class(fpm_cmd_settings), optional, intent(in) :: settings
character(len=:), allocatable, intent(out) :: working_dir
character(len=:), allocatable, intent(out) :: working_dir_
if (present(settings)) then
working_dir = settings%working_dir
working_dir_ = settings%working_dir
end if
end subroutine get_working_dir

Expand Down
2 changes: 2 additions & 0 deletions fpm.toml
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,8 @@ toml-f.git = "https://github.com/toml-f/toml-f"
toml-f.rev = "54686e45993f3a9a1d05d5c7419f39e7d5a4eb3f"
M_CLI2.git = "https://github.com/urbanjost/M_CLI2.git"
M_CLI2.rev = "7264878cdb1baff7323cc48596d829ccfe7751b8"
jonquil.git = "https://github.com/toml-f/jonquil"
jonquil.rev = "05d30818bb12fb877226ce284b9a3a41b971a889"

[[test]]
name = "cli-test"
Expand Down
26 changes: 10 additions & 16 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -17,8 +17,7 @@ module fpm


use fpm_sources, only: add_executable_sources, add_sources_from_dir
use fpm_targets, only: targets_from_sources, &
resolve_target_linking, build_target_t, build_target_ptr, &
use fpm_targets, only: targets_from_sources, build_target_t, build_target_ptr, &
FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE
use fpm_manifest, only : get_package_data, package_config_t
use fpm_error, only : error_t, fatal_error, fpm_stop
Expand All @@ -33,10 +32,8 @@ module fpm

contains


!> Constructs a valid fpm model from command line settings and the toml manifest.
subroutine build_model(model, settings, package, error)
! Constructs a valid fpm model from command line settings and toml manifest
!
type(fpm_model_t), intent(out) :: model
type(fpm_build_settings), intent(in) :: settings
type(package_config_t), intent(in) :: package
Expand All @@ -45,9 +42,7 @@ subroutine build_model(model, settings, package, error)
integer :: i, j
type(package_config_t) :: dependency
character(len=:), allocatable :: manifest, lib_dir, flags, cflags, cxxflags, ldflags
character(len=:), allocatable :: version
logical :: has_cpp

logical :: duplicates_found = .false.
type(string_t) :: include_dir

Expand Down Expand Up @@ -117,8 +112,7 @@ subroutine build_model(model, settings, package, error)
features%implicit_external = dependency%fortran%implicit_external
features%source_form = dependency%fortran%source_form
end associate
call package%version%to_string(version)
model%packages(i)%version = version
model%packages(i)%version = package%version%s()

if (allocated(dependency%preprocess)) then
do j = 1, size(dependency%preprocess)
Expand Down Expand Up @@ -239,7 +233,6 @@ subroutine build_model(model, settings, package, error)

endif


if (settings%verbose) then
write(*,*)'<INFO> BUILD_NAME: ',model%build_prefix
write(*,*)'<INFO> COMPILER: ',model%compiler%fc
Expand Down Expand Up @@ -402,6 +395,7 @@ end subroutine check_module_names

subroutine cmd_build(settings)
type(fpm_build_settings), intent(in) :: settings

type(package_config_t) :: package
type(fpm_model_t) :: model
type(build_target_ptr), allocatable :: targets(:)
Expand All @@ -411,17 +405,17 @@ subroutine cmd_build(settings)

call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
if (allocated(error)) then
call fpm_stop(1,'*cmd_build*:package error:'//error%message)
call fpm_stop(1,'*cmd_build* Package error: '//error%message)
end if

call build_model(model, settings, package, error)
if (allocated(error)) then
call fpm_stop(1,'*cmd_build*:model error:'//error%message)
call fpm_stop(1,'*cmd_build* Model error: '//error%message)
end if

call targets_from_sources(targets, model, settings%prune, error)
if (allocated(error)) then
call fpm_stop(1,'*cmd_build*:target error:'//error%message)
call fpm_stop(1,'*cmd_build* Target error: '//error%message)
end if

if(settings%list)then
Expand Down Expand Up @@ -457,17 +451,17 @@ subroutine cmd_run(settings,test)

call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
if (allocated(error)) then
call fpm_stop(1, '*cmd_run*:package error:'//error%message)
call fpm_stop(1, '*cmd_run* Package error: '//error%message)
end if

call build_model(model, settings%fpm_build_settings, package, error)
if (allocated(error)) then
call fpm_stop(1, '*cmd_run*:model error:'//error%message)
call fpm_stop(1, '*cmd_run* Model error: '//error%message)
end if

call targets_from_sources(targets, model, settings%prune, error)
if (allocated(error)) then
call fpm_stop(1, '*cmd_run*:targets error:'//error%message)
call fpm_stop(1, '*cmd_run* Targets error: '//error%message)
end if

if (test) then
Expand Down
8 changes: 2 additions & 6 deletions src/fpm/cmd/install.f90
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,6 @@ subroutine cmd_install(settings)
type(fpm_model_t) :: model
type(build_target_ptr), allocatable :: targets(:)
type(installer_t) :: installer
character(len=:), allocatable :: lib, dir
type(string_t), allocatable :: list(:)
logical :: installable

Expand All @@ -49,7 +48,7 @@ subroutine cmd_install(settings)
end if

if (settings%list) then
call install_info(output_unit, package, model, targets)
call install_info(output_unit, targets)
return
end if

Expand Down Expand Up @@ -81,14 +80,11 @@ subroutine cmd_install(settings)

end subroutine cmd_install

subroutine install_info(unit, package, model, targets)
subroutine install_info(unit, targets)
integer, intent(in) :: unit
type(package_config_t), intent(in) :: package
type(fpm_model_t), intent(in) :: model
type(build_target_ptr), intent(in) :: targets(:)

integer :: ii, ntargets
character(len=:), allocatable :: lib
type(string_t), allocatable :: install_target(:), temp(:)

allocate(install_target(0))
Expand Down
2 changes: 1 addition & 1 deletion src/fpm/cmd/new.f90
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ module fpm_cmd_new
use fpm_command_line, only : fpm_new_settings
use fpm_environment, only : OS_LINUX, OS_MACOS, OS_WINDOWS
use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir
use fpm_filesystem, only : fileopen, fileclose, filewrite, warnwrite, which, run
use fpm_filesystem, only : fileopen, fileclose, warnwrite, which, run
use fpm_strings, only : join, to_fortran_name
use fpm_error, only : fpm_stop

Expand Down
Loading

0 comments on commit 4ba0bf9

Please sign in to comment.