Skip to content

Commit b443ce5

Browse files
authored
Enter custom path to the config file via command line (#945)
2 parents fe1fd6e + c8e65d3 commit b443ce5

File tree

5 files changed

+142
-75
lines changed

5 files changed

+142
-75
lines changed

src/fpm.f90

+2-1
Original file line numberDiff line numberDiff line change
@@ -78,7 +78,8 @@ subroutine build_model(model, settings, package, error)
7878
if (allocated(error)) return
7979

8080
! Create dependencies
81-
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"))
81+
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"), &
82+
& path_to_config=settings%path_to_config)
8283

8384
! Build and resolve model dependencies
8485
call model%deps%add(package, error)

src/fpm/cmd/update.f90

+2-2
Original file line numberDiff line numberDiff line change
@@ -33,8 +33,8 @@ subroutine cmd_update(settings)
3333
cache = join_path("build", "cache.toml")
3434
if (settings%clean) call delete_file(cache)
3535

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

3939
call deps%add(package, error)
4040
call handle_error(error)

src/fpm/dependency.f90

+25-3
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, serializable_t
6464
use fpm_manifest, only: package_config_t, dependency_config_t, get_package_data
6565
use fpm_manifest_dependency, only: manifest_has_changed, dependency_destroy
@@ -130,6 +130,8 @@ module fpm_dependency
130130
type(dependency_node_t), allocatable :: dep(:)
131131
!> Cache file
132132
character(len=:), allocatable :: cache
133+
!> Custom path to the global config file
134+
character(len=:), allocatable :: path_to_config
133135

134136
contains
135137

@@ -198,13 +200,15 @@ module fpm_dependency
198200
contains
199201

200202
!> Create a new dependency tree
201-
subroutine new_dependency_tree(self, verbosity, cache)
203+
subroutine new_dependency_tree(self, verbosity, cache, path_to_config)
202204
!> Instance of the dependency tree
203205
type(dependency_tree_t), intent(out) :: self
204206
!> Verbosity of printout
205207
integer, intent(in), optional :: verbosity
206208
!> Name of the cache file
207209
character(len=*), intent(in), optional :: cache
210+
!> Path to the global config file.
211+
character(len=*), intent(in), optional :: path_to_config
208212

209213
call resize(self%dep)
210214
self%dep_dir = join_path("build", "dependencies")
@@ -213,6 +217,8 @@ subroutine new_dependency_tree(self, verbosity, cache)
213217

214218
if (present(cache)) self%cache = cache
215219

220+
if (present(path_to_config)) self%path_to_config = path_to_config
221+
216222
end subroutine new_dependency_tree
217223

218224
!> Create a new dependency node from a configuration
@@ -566,8 +572,24 @@ subroutine resolve_dependencies(self, root, error)
566572
type(error_t), allocatable, intent(out) :: error
567573

568574
type(fpm_global_settings) :: global_settings
575+
character(:), allocatable :: parent_directory
569576
integer :: ii
570577

578+
! Register path to global config file if it was entered via the command line.
579+
if (allocated(self%path_to_config)) then
580+
if (len_trim(self%path_to_config) > 0) then
581+
parent_directory = parent_dir(self%path_to_config)
582+
583+
if (len_trim(parent_directory) == 0) then
584+
global_settings%path_to_config_folder = "."
585+
else
586+
global_settings%path_to_config_folder = parent_directory
587+
end if
588+
589+
global_settings%config_file_name = basename(self%path_to_config)
590+
end if
591+
end if
592+
571593
call get_global_settings(global_settings, error)
572594
if (allocated(error)) return
573595

@@ -695,7 +717,7 @@ subroutine get_from_registry(self, target_dir, global_settings, error, downloade
695717
end if
696718

697719
! Include namespace and package name in the target url and download package data.
698-
target_url = global_settings%registry_settings%url//'packages/'//self%namespace//'/'//self%name
720+
target_url = global_settings%registry_settings%url//'/packages/'//self%namespace//'/'//self%name
699721
call downloader%get_pkg_data(target_url, self%requested_version, tmp_file, json, error)
700722
close (unit, status='delete')
701723
if (allocated(error)) return

src/fpm/downloader.f90

+1-1
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ module fpm_downloader
1818

1919
contains
2020

21-
!> Perform an http get request, save output to file, and parse json.
21+
!> Perform an http get request, save output to file, and parse json.
2222
subroutine get_pkg_data(url, version, tmp_pkg_file, json, error)
2323
character(*), intent(in) :: url
2424
type(version_t), allocatable, intent(in) :: version

0 commit comments

Comments
 (0)