Skip to content

Commit f3150e3

Browse files
committed
Enter path to global config file via the command line
1 parent 4d7ba17 commit f3150e3

File tree

6 files changed

+137
-84
lines changed

6 files changed

+137
-84
lines changed

src/fpm.f90

Lines changed: 15 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,6 @@ subroutine build_model(model, settings, package, error)
4242
integer :: i, j
4343
type(package_config_t) :: dependency
4444
character(len=:), allocatable :: manifest, lib_dir
45-
character(len=:), allocatable :: version
4645
logical :: has_cpp
4746
logical :: duplicates_found
4847
type(string_t) :: include_dir
@@ -75,7 +74,8 @@ subroutine build_model(model, settings, package, error)
7574
if (allocated(error)) return
7675

7776
! Create dependencies
78-
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"))
77+
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"), &
78+
& path_to_config=settings%path_to_config)
7979

8080
! Build and resolve model dependencies
8181
call model%deps%add(package, error)
@@ -324,7 +324,7 @@ end subroutine check_modules_for_duplicates
324324
subroutine check_module_names(model, error)
325325
type(fpm_model_t), intent(in) :: model
326326
type(error_t), allocatable, intent(out) :: error
327-
integer :: i,j,k,l,m
327+
integer :: k,l,m
328328
logical :: valid,errors_found,enforce_this_file
329329
type(string_t) :: package_name,module_name,package_prefix
330330

@@ -621,13 +621,13 @@ subroutine cmd_run(settings,test)
621621
contains
622622
subroutine compact_list_all()
623623
integer, parameter :: LINE_WIDTH = 80
624-
integer :: i, j, nCol
625-
j = 1
624+
integer :: ii, jj, nCol
625+
jj = 1
626626
nCol = LINE_WIDTH/col_width
627627
write(stderr,*) 'Available names:'
628-
do i=1,size(targets)
628+
do ii=1,size(targets)
629629

630-
exe_target => targets(i)%ptr
630+
exe_target => targets(ii)%ptr
631631

632632
if (exe_target%target_type == FPM_TARGET_EXECUTABLE .and. &
633633
allocated(exe_target%dependencies)) then
@@ -636,9 +636,9 @@ subroutine compact_list_all()
636636

637637
if (exe_source%unit_scope == run_scope) then
638638

639-
write(stderr,'(A)',advance=(merge("yes","no ",modulo(j,nCol)==0))) &
639+
write(stderr,'(A)',advance=(merge("yes","no ",modulo(jj,nCol)==0))) &
640640
& [character(len=col_width) :: basename(exe_target%output_file, suffix=.false.)]
641-
j = j + 1
641+
jj = jj + 1
642642

643643
end if
644644
end if
@@ -648,14 +648,14 @@ end subroutine compact_list_all
648648

649649
subroutine compact_list()
650650
integer, parameter :: LINE_WIDTH = 80
651-
integer :: i, j, nCol
652-
j = 1
651+
integer :: ii, jj, nCol
652+
jj = 1
653653
nCol = LINE_WIDTH/col_width
654654
write(stderr,*) 'Matched names:'
655-
do i=1,size(executables)
656-
write(stderr,'(A)',advance=(merge("yes","no ",modulo(j,nCol)==0))) &
657-
& [character(len=col_width) :: basename(executables(i)%s, suffix=.false.)]
658-
j = j + 1
655+
do ii=1,size(executables)
656+
write(stderr,'(A)',advance=(merge("yes","no ",modulo(jj,nCol)==0))) &
657+
& [character(len=col_width) :: basename(executables(ii)%s, suffix=.false.)]
658+
jj = jj + 1
659659
enddo
660660
write(stderr,*)
661661
end subroutine compact_list

src/fpm/cmd/update.f90

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -24,18 +24,16 @@ subroutine cmd_update(settings)
2424
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
2525
call handle_error(error)
2626

27-
if (.not.exists("build")) then
27+
if (.not. exists("build")) then
2828
call mkdir("build")
2929
call filewrite(join_path("build", ".gitignore"),["*"])
3030
end if
3131

3232
cache = join_path("build", "cache.toml")
33-
if (settings%clean) then
34-
call delete_file(cache)
35-
end if
33+
if (settings%clean) call delete_file(cache)
3634

37-
call new_dependency_tree(deps, cache=cache, &
38-
verbosity=merge(2, 1, settings%verbose))
35+
call new_dependency_tree(deps, cache=cache, verbosity=merge(2, 1, settings%verbose), &
36+
& path_to_config=settings%path_to_config)
3937

4038
call deps%add(package, error)
4139
call handle_error(error)

src/fpm/dependency.f90

Lines changed: 51 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -59,7 +59,7 @@ module fpm_dependency
5959
use fpm_environment, only: get_os_type, OS_WINDOWS, os_is_unix
6060
use fpm_error, only: error_t, fatal_error
6161
use fpm_filesystem, only: exists, join_path, mkdir, canon_path, windows_path, list_files, is_dir, basename, &
62-
os_delete_dir, get_temp_filename
62+
os_delete_dir, get_temp_filename, parent_dir
6363
use fpm_git, only: git_target_revision, git_target_default, git_revision, operator(==)
6464
use fpm_manifest, only: package_config_t, dependency_config_t, get_package_data
6565
use fpm_manifest_dependency, only: manifest_has_changed
@@ -123,7 +123,11 @@ module fpm_dependency
123123
type(dependency_node_t), allocatable :: dep(:)
124124
!> Cache file
125125
character(len=:), allocatable :: cache
126+
!> Custom path to the global config file
127+
character(len=:), allocatable :: path_to_config
128+
126129
contains
130+
127131
!> Overload procedure to add new dependencies to the tree
128132
generic :: add => add_project, add_project_dependencies, add_dependencies, &
129133
add_dependency, add_dependency_node
@@ -183,24 +187,24 @@ module fpm_dependency
183187
contains
184188

185189
!> Create a new dependency tree
186-
subroutine new_dependency_tree(self, verbosity, cache)
190+
subroutine new_dependency_tree(self, verbosity, cache, path_to_config)
187191
!> Instance of the dependency tree
188192
type(dependency_tree_t), intent(out) :: self
189193
!> Verbosity of printout
190194
integer, intent(in), optional :: verbosity
191195
!> Name of the cache file
192196
character(len=*), intent(in), optional :: cache
197+
!> Path to the global config file.
198+
character(len=*), intent(in), optional :: path_to_config
193199

194200
call resize(self%dep)
195201
self%dep_dir = join_path("build", "dependencies")
196202

197-
if (present(verbosity)) then
198-
self%verbosity = verbosity
199-
end if
203+
if (present(verbosity)) self%verbosity = verbosity
200204

201-
if (present(cache)) then
202-
self%cache = cache
203-
end if
205+
if (present(cache)) self%cache = cache
206+
207+
if (present(path_to_config)) self%path_to_config = path_to_config
204208

205209
end subroutine new_dependency_tree
206210

@@ -311,15 +315,15 @@ subroutine add_project(self, package, error)
311315

312316
! After resolving all dependencies, check if we have cached ones to avoid updates
313317
if (allocated(self%cache)) then
314-
call new_dependency_tree(cached, verbosity=self%verbosity,cache=self%cache)
318+
call new_dependency_tree(cached, verbosity=self%verbosity, cache=self%cache)
315319
call cached%load(self%cache, error)
316320
if (allocated(error)) return
317321

318322
! Skip root node
319-
do id=2,cached%ndep
320-
cached%dep(id)%cached = .true.
321-
call self%add(cached%dep(id), error)
322-
if (allocated(error)) return
323+
do id = 2, cached%ndep
324+
cached%dep(id)%cached = .true.
325+
call self%add(cached%dep(id), error)
326+
if (allocated(error)) return
323327
end do
324328
end if
325329

@@ -443,13 +447,13 @@ subroutine add_dependency_node(self, dependency, error)
443447
! the manifest has priority
444448
if (dependency%cached) then
445449
if (dependency_has_changed(dependency, self%dep(id), self%verbosity, self%unit)) then
446-
if (self%verbosity>0) write (self%unit, out_fmt) "Dependency change detected:", dependency%name
447-
self%dep(id)%update = .true.
450+
if (self%verbosity > 0) write (self%unit, out_fmt) "Dependency change detected:", dependency%name
451+
self%dep(id)%update = .true.
448452
else
449-
! Store the cached one
450-
self%dep(id) = dependency
451-
self%dep(id)%update = .false.
452-
endif
453+
! Store the cached one
454+
self%dep(id) = dependency
455+
self%dep(id)%update = .false.
456+
end if
453457
end if
454458
else
455459
! New dependency: add from scratch
@@ -498,7 +502,7 @@ subroutine update_dependency(self, name, error)
498502

499503
associate (dep => self%dep(id))
500504
if (allocated(dep%git) .and. dep%update) then
501-
if (self%verbosity>0) write (self%unit, out_fmt) "Update:", dep%name
505+
if (self%verbosity > 0) write (self%unit, out_fmt) "Update:", dep%name
502506
proj_dir = join_path(self%dep_dir, dep%name)
503507
call dep%git%checkout(proj_dir, error)
504508
if (allocated(error)) return
@@ -545,8 +549,24 @@ subroutine resolve_dependencies(self, root, error)
545549
type(error_t), allocatable, intent(out) :: error
546550

547551
type(fpm_global_settings) :: global_settings
552+
character(:), allocatable :: parent_directory
548553
integer :: ii
549554

555+
! Register path to global config file if it was entered via the command line.
556+
if (allocated(self%path_to_config)) then
557+
if (len_trim(self%path_to_config) > 0) then
558+
parent_directory = parent_dir(self%path_to_config)
559+
560+
if (len_trim(parent_directory) == 0) then
561+
global_settings%path_to_config_folder = "."
562+
else
563+
global_settings%path_to_config_folder = parent_directory
564+
end if
565+
566+
global_settings%config_file_name = basename(self%path_to_config)
567+
end if
568+
end if
569+
550570
call get_global_settings(global_settings, error)
551571
if (allocated(error)) return
552572

@@ -722,7 +742,7 @@ subroutine check_and_read_pkg_data(json, node, download_url, version, error)
722742
character(:), allocatable :: version_key, version_str, error_message, namespace, name
723743

724744
namespace = ""
725-
name = "UNNAMED_NODE"
745+
name = "UNNAMED_NODE"
726746
if (allocated(node%namespace)) namespace = node%namespace
727747
if (allocated(node%name)) name = node%name
728748

@@ -1199,27 +1219,27 @@ logical function dependency_has_changed(cached, manifest, verbosity, iunit) resu
11991219
!> may not have it
12001220
if (allocated(cached%version) .and. allocated(manifest%version)) then
12011221
if (cached%version /= manifest%version) then
1202-
if (verbosity>1) write(iunit,out_fmt) "VERSION has changed: "//cached%version%s()//" vs. "//manifest%version%s()
1203-
return
1204-
endif
1222+
if (verbosity > 1) write (iunit, out_fmt) "VERSION has changed: "//cached%version%s()//" vs. "//manifest%version%s()
1223+
return
1224+
end if
12051225
else
1206-
if (verbosity>1) write(iunit,out_fmt) "VERSION has changed presence "
1226+
if (verbosity > 1) write (iunit, out_fmt) "VERSION has changed presence "
12071227
end if
12081228
if (allocated(cached%revision) .and. allocated(manifest%revision)) then
12091229
if (cached%revision /= manifest%revision) then
1210-
if (verbosity>1) write(iunit,out_fmt) "REVISION has changed: "//cached%revision//" vs. "//manifest%revision
1230+
if (verbosity > 1) write (iunit, out_fmt) "REVISION has changed: "//cached%revision//" vs. "//manifest%revision
12111231
return
1212-
endif
1232+
end if
12131233
else
1214-
if (verbosity>1) write(iunit,out_fmt) "REVISION has changed presence "
1234+
if (verbosity > 1) write (iunit, out_fmt) "REVISION has changed presence "
12151235
end if
12161236
if (allocated(cached%proj_dir) .and. allocated(manifest%proj_dir)) then
12171237
if (cached%proj_dir /= manifest%proj_dir) then
1218-
if (verbosity>1) write(iunit,out_fmt) "PROJECT DIR has changed: "//cached%proj_dir//" vs. "//manifest%proj_dir
1238+
if (verbosity > 1) write (iunit, out_fmt) "PROJECT DIR has changed: "//cached%proj_dir//" vs. "//manifest%proj_dir
12191239
return
1220-
endif
1240+
end if
12211241
else
1222-
if (verbosity>1) write(iunit,out_fmt) "PROJECT DIR has changed presence "
1242+
if (verbosity > 1) write (iunit, out_fmt) "PROJECT DIR has changed presence "
12231243
end if
12241244

12251245
!> All checks passed: the two dependencies have no differences

0 commit comments

Comments
 (0)