Skip to content

Commit 4ba0bf9

Browse files
authored
Merge pull request #817 from minhqdao/resolve-config-file
Add global config file, implement local and remote registry
2 parents ef6532b + e1eb03b commit 4ba0bf9

27 files changed

+3671
-732
lines changed

app/main.f90

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -99,20 +99,20 @@ function has_manifest(dir)
9999
has_manifest = exists(join_path(dir, "fpm.toml"))
100100
end function has_manifest
101101

102-
subroutine handle_error(error)
103-
type(error_t), optional, intent(in) :: error
104-
if (present(error)) then
105-
write(error_unit, '("[Error]", 1x, a)') error%message
102+
subroutine handle_error(error_)
103+
type(error_t), optional, intent(in) :: error_
104+
if (present(error_)) then
105+
write (error_unit, '("[Error]", 1x, a)') error_%message
106106
stop 1
107107
end if
108108
end subroutine handle_error
109109

110110
!> Save access to working directory in settings, in case setting have not been allocated
111-
subroutine get_working_dir(settings, working_dir)
111+
subroutine get_working_dir(settings, working_dir_)
112112
class(fpm_cmd_settings), optional, intent(in) :: settings
113-
character(len=:), allocatable, intent(out) :: working_dir
113+
character(len=:), allocatable, intent(out) :: working_dir_
114114
if (present(settings)) then
115-
working_dir = settings%working_dir
115+
working_dir_ = settings%working_dir
116116
end if
117117
end subroutine get_working_dir
118118

fpm.toml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,8 @@ toml-f.git = "https://github.com/toml-f/toml-f"
1010
toml-f.rev = "54686e45993f3a9a1d05d5c7419f39e7d5a4eb3f"
1111
M_CLI2.git = "https://github.com/urbanjost/M_CLI2.git"
1212
M_CLI2.rev = "7264878cdb1baff7323cc48596d829ccfe7751b8"
13+
jonquil.git = "https://github.com/toml-f/jonquil"
14+
jonquil.rev = "05d30818bb12fb877226ce284b9a3a41b971a889"
1315

1416
[[test]]
1517
name = "cli-test"

src/fpm.f90

Lines changed: 10 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,7 @@ module fpm
1717

1818

1919
use fpm_sources, only: add_executable_sources, add_sources_from_dir
20-
use fpm_targets, only: targets_from_sources, &
21-
resolve_target_linking, build_target_t, build_target_ptr, &
20+
use fpm_targets, only: targets_from_sources, build_target_t, build_target_ptr, &
2221
FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE
2322
use fpm_manifest, only : get_package_data, package_config_t
2423
use fpm_error, only : error_t, fatal_error, fpm_stop
@@ -33,10 +32,8 @@ module fpm
3332

3433
contains
3534

36-
35+
!> Constructs a valid fpm model from command line settings and the toml manifest.
3736
subroutine build_model(model, settings, package, error)
38-
! Constructs a valid fpm model from command line settings and toml manifest
39-
!
4037
type(fpm_model_t), intent(out) :: model
4138
type(fpm_build_settings), intent(in) :: settings
4239
type(package_config_t), intent(in) :: package
@@ -45,9 +42,7 @@ subroutine build_model(model, settings, package, error)
4542
integer :: i, j
4643
type(package_config_t) :: dependency
4744
character(len=:), allocatable :: manifest, lib_dir, flags, cflags, cxxflags, ldflags
48-
character(len=:), allocatable :: version
4945
logical :: has_cpp
50-
5146
logical :: duplicates_found = .false.
5247
type(string_t) :: include_dir
5348

@@ -117,8 +112,7 @@ subroutine build_model(model, settings, package, error)
117112
features%implicit_external = dependency%fortran%implicit_external
118113
features%source_form = dependency%fortran%source_form
119114
end associate
120-
call package%version%to_string(version)
121-
model%packages(i)%version = version
115+
model%packages(i)%version = package%version%s()
122116

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

240234
endif
241235

242-
243236
if (settings%verbose) then
244237
write(*,*)'<INFO> BUILD_NAME: ',model%build_prefix
245238
write(*,*)'<INFO> COMPILER: ',model%compiler%fc
@@ -402,6 +395,7 @@ end subroutine check_module_names
402395

403396
subroutine cmd_build(settings)
404397
type(fpm_build_settings), intent(in) :: settings
398+
405399
type(package_config_t) :: package
406400
type(fpm_model_t) :: model
407401
type(build_target_ptr), allocatable :: targets(:)
@@ -411,17 +405,17 @@ subroutine cmd_build(settings)
411405

412406
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
413407
if (allocated(error)) then
414-
call fpm_stop(1,'*cmd_build*:package error:'//error%message)
408+
call fpm_stop(1,'*cmd_build* Package error: '//error%message)
415409
end if
416410

417411
call build_model(model, settings, package, error)
418412
if (allocated(error)) then
419-
call fpm_stop(1,'*cmd_build*:model error:'//error%message)
413+
call fpm_stop(1,'*cmd_build* Model error: '//error%message)
420414
end if
421415

422416
call targets_from_sources(targets, model, settings%prune, error)
423417
if (allocated(error)) then
424-
call fpm_stop(1,'*cmd_build*:target error:'//error%message)
418+
call fpm_stop(1,'*cmd_build* Target error: '//error%message)
425419
end if
426420

427421
if(settings%list)then
@@ -457,17 +451,17 @@ subroutine cmd_run(settings,test)
457451

458452
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
459453
if (allocated(error)) then
460-
call fpm_stop(1, '*cmd_run*:package error:'//error%message)
454+
call fpm_stop(1, '*cmd_run* Package error: '//error%message)
461455
end if
462456

463457
call build_model(model, settings%fpm_build_settings, package, error)
464458
if (allocated(error)) then
465-
call fpm_stop(1, '*cmd_run*:model error:'//error%message)
459+
call fpm_stop(1, '*cmd_run* Model error: '//error%message)
466460
end if
467461

468462
call targets_from_sources(targets, model, settings%prune, error)
469463
if (allocated(error)) then
470-
call fpm_stop(1, '*cmd_run*:targets error:'//error%message)
464+
call fpm_stop(1, '*cmd_run* Targets error: '//error%message)
471465
end if
472466

473467
if (test) then

src/fpm/cmd/install.f90

Lines changed: 2 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,6 @@ subroutine cmd_install(settings)
2828
type(fpm_model_t) :: model
2929
type(build_target_ptr), allocatable :: targets(:)
3030
type(installer_t) :: installer
31-
character(len=:), allocatable :: lib, dir
3231
type(string_t), allocatable :: list(:)
3332
logical :: installable
3433

@@ -49,7 +48,7 @@ subroutine cmd_install(settings)
4948
end if
5049

5150
if (settings%list) then
52-
call install_info(output_unit, package, model, targets)
51+
call install_info(output_unit, targets)
5352
return
5453
end if
5554

@@ -81,14 +80,11 @@ subroutine cmd_install(settings)
8180

8281
end subroutine cmd_install
8382

84-
subroutine install_info(unit, package, model, targets)
83+
subroutine install_info(unit, targets)
8584
integer, intent(in) :: unit
86-
type(package_config_t), intent(in) :: package
87-
type(fpm_model_t), intent(in) :: model
8885
type(build_target_ptr), intent(in) :: targets(:)
8986

9087
integer :: ii, ntargets
91-
character(len=:), allocatable :: lib
9288
type(string_t), allocatable :: install_target(:), temp(:)
9389

9490
allocate(install_target(0))

src/fpm/cmd/new.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,7 @@ module fpm_cmd_new
5656
use fpm_command_line, only : fpm_new_settings
5757
use fpm_environment, only : OS_LINUX, OS_MACOS, OS_WINDOWS
5858
use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir
59-
use fpm_filesystem, only : fileopen, fileclose, filewrite, warnwrite, which, run
59+
use fpm_filesystem, only : fileopen, fileclose, warnwrite, which, run
6060
use fpm_strings, only : join, to_fortran_name
6161
use fpm_error, only : fpm_stop
6262

0 commit comments

Comments
 (0)