Skip to content

Commit

Permalink
Merge branch 'main' into custom-path-to-config
Browse files Browse the repository at this point in the history
# Conflicts:
#	src/fpm.f90
#	src/fpm/dependency.f90
#	src/fpm_settings.f90
  • Loading branch information
minhqdao committed Jun 19, 2023
2 parents 5409778 + e70422f commit f088c38
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 22 deletions.
8 changes: 4 additions & 4 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -617,8 +617,10 @@ subroutine cmd_run(settings,test)
call fpm_stop(stat(firsterror),'*cmd_run*:stopping due to failed executions')
end if

endif
end if

contains

subroutine compact_list_all()
integer, parameter :: LINE_WIDTH = 80
integer :: ii, jj, nCol
Expand All @@ -635,11 +637,9 @@ subroutine compact_list_all()
exe_source => exe_target%dependencies(1)%ptr%source

if (exe_source%unit_scope == run_scope) then

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

end if
end if
end do
Expand All @@ -656,7 +656,7 @@ subroutine compact_list()
write(stderr,'(A)',advance=(merge("yes","no ",modulo(jj,nCol)==0))) &
& [character(len=col_width) :: basename(executables(ii)%s, suffix=.false.)]
jj = jj + 1
enddo
end do
write(stderr,*)
end subroutine compact_list

Expand Down
34 changes: 16 additions & 18 deletions src/fpm_settings.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,8 @@ module fpm_settings
use fpm_environment, only: os_is_unix
use fpm_error, only: error_t, fatal_error
use fpm_toml, only: toml_table, toml_error, toml_stat, get_value, toml_load, check_keys
use fpm_os, only: get_current_directory, change_directory, get_absolute_path, &
convert_to_absolute_path
use fpm_os, only: get_current_directory, change_directory, get_absolute_path, convert_to_absolute_path

implicit none
private
public :: fpm_global_settings, get_global_settings, get_registry_settings, official_registry_base_url
Expand All @@ -21,7 +21,7 @@ module fpm_settings
!> Registry configs.
type(fpm_registry_settings), allocatable :: registry_settings
contains
procedure :: has_custom_location, full_path
procedure :: has_custom_location, full_path, path_to_config_folder_or_empty
end type

type :: fpm_registry_settings
Expand Down Expand Up @@ -57,8 +57,8 @@ subroutine get_global_settings(global_settings, error)
! Use custom path to the config file if it was specified.
if (global_settings%has_custom_location()) then
! Throw error if folder doesn't exist.
if (.not. exists(config_path(global_settings))) then
call fatal_error(error, "Folder not found: '"//config_path(global_settings)//"'."); return
if (.not. exists(global_settings%path_to_config_folder)) then
call fatal_error(error, "Folder not found: '"//global_settings%path_to_config_folder//"'."); return
end if

! Throw error if the file doesn't exist.
Expand Down Expand Up @@ -106,7 +106,6 @@ subroutine get_global_settings(global_settings, error)
else
call use_default_registry_settings(global_settings)
end if

end

!> Default registry settings are typically applied if the config file doesn't exist or no registry table was found in
Expand All @@ -116,7 +115,7 @@ subroutine use_default_registry_settings(global_settings)

allocate (global_settings%registry_settings)
global_settings%registry_settings%url = official_registry_base_url
global_settings%registry_settings%cache_path = join_path(config_path(global_settings), &
global_settings%registry_settings%cache_path = join_path(global_settings%path_to_config_folder_or_empty(), &
& 'dependencies')
end

Expand Down Expand Up @@ -156,7 +155,7 @@ subroutine get_registry_settings(table, global_settings, error)
global_settings%registry_settings%path = path
else
! Get canonical, absolute path on both Unix and Windows.
call get_absolute_path(join_path(config_path(global_settings), path), &
call get_absolute_path(join_path(global_settings%path_to_config_folder_or_empty(), path), &
& global_settings%registry_settings%path, error)
if (allocated(error)) return

Expand Down Expand Up @@ -202,20 +201,20 @@ subroutine get_registry_settings(table, global_settings, error)
if (.not. exists(cache_path)) call mkdir(cache_path)
global_settings%registry_settings%cache_path = cache_path
else
cache_path = join_path(config_path(global_settings), cache_path)
cache_path = join_path(global_settings%path_to_config_folder_or_empty(), cache_path)
if (.not. exists(cache_path)) call mkdir(cache_path)
! Get canonical, absolute path on both Unix and Windows.
call get_absolute_path(cache_path, global_settings%registry_settings%cache_path, error)
if (allocated(error)) return
end if
else if (.not. allocated(path)) then
global_settings%registry_settings%cache_path = join_path(config_path(global_settings), &
& 'dependencies')
global_settings%registry_settings%cache_path = &
join_path(global_settings%path_to_config_folder_or_empty(), 'dependencies')
end if
end

!> True if the global config file is not at the default location.
pure logical function has_custom_location(self)
elemental logical function has_custom_location(self)
class(fpm_global_settings), intent(in) :: self

has_custom_location = allocated(self%path_to_config_folder) .and. allocated(self%config_file_name)
Expand All @@ -228,19 +227,18 @@ function full_path(self) result(result)
class(fpm_global_settings), intent(in) :: self
character(len=:), allocatable :: result

result = join_path(config_path(self), self%config_file_name)
result = join_path(self%path_to_config_folder_or_empty(), self%config_file_name)
end

!> The path to the global config directory.
function config_path(self)
pure function path_to_config_folder_or_empty(self)
class(fpm_global_settings), intent(in) :: self
character(len=:), allocatable :: config_path
character(len=:), allocatable :: path_to_config_folder_or_empty

if (allocated(self%path_to_config_folder)) then
config_path = self%path_to_config_folder
path_to_config_folder_or_empty = self%path_to_config_folder
else
config_path = ""
path_to_config_folder_or_empty = ""
end if
end

end

0 comments on commit f088c38

Please sign in to comment.