@@ -4,13 +4,14 @@ module fpm_settings
4
4
use fpm_environment, only: os_is_unix
5
5
use fpm_error, only: error_t, fatal_error
6
6
use fpm_toml, only: toml_table, toml_error, toml_stat, get_value, toml_load, check_keys
7
- use fpm_os, only: get_current_directory, change_directory, get_absolute_path, &
8
- convert_to_absolute_path
7
+ use fpm_os, only: get_current_directory, change_directory, get_absolute_path, convert_to_absolute_path
8
+
9
9
implicit none
10
10
private
11
11
public :: fpm_global_settings, get_global_settings, get_registry_settings, official_registry_base_url
12
12
13
13
character (* ), parameter :: official_registry_base_url = ' https://registry-apis.vercel.app'
14
+ character (* ), parameter :: default_config_file_name = ' config.toml'
14
15
15
16
type :: fpm_global_settings
16
17
! > Path to the global config file excluding the file name.
@@ -20,7 +21,7 @@ module fpm_settings
20
21
! > Registry configs.
21
22
type (fpm_registry_settings), allocatable :: registry_settings
22
23
contains
23
- procedure :: has_custom_location, full_path
24
+ procedure :: has_custom_location, full_path, path_to_config_folder_or_empty
24
25
end type
25
26
26
27
type :: fpm_registry_settings
@@ -56,8 +57,8 @@ subroutine get_global_settings(global_settings, error)
56
57
! Use custom path to the config file if it was specified.
57
58
if (global_settings% has_custom_location()) then
58
59
! Throw error if folder doesn't exist.
59
- if (.not. exists(config_path( global_settings) )) then
60
- call fatal_error(error, " Folder not found: '" // config_path( global_settings) // " '." ); return
60
+ if (.not. exists(global_settings% path_to_config_folder )) then
61
+ call fatal_error(error, " Folder not found: '" // global_settings% path_to_config_folder // " '." ); return
61
62
end if
62
63
63
64
! Throw error if the file doesn't exist.
@@ -77,7 +78,7 @@ subroutine get_global_settings(global_settings, error)
77
78
end if
78
79
79
80
! Use default file name.
80
- global_settings% config_file_name = ' config.toml '
81
+ global_settings% config_file_name = default_config_file_name
81
82
82
83
! Apply default registry settings and return if config file doesn't exist.
83
84
if (.not. exists(global_settings% full_path())) then
@@ -105,8 +106,7 @@ subroutine get_global_settings(global_settings, error)
105
106
else
106
107
call use_default_registry_settings(global_settings)
107
108
end if
108
-
109
- end subroutine get_global_settings
109
+ end
110
110
111
111
! > Default registry settings are typically applied if the config file doesn't exist or no registry table was found in
112
112
! > the global config file.
@@ -115,9 +115,9 @@ subroutine use_default_registry_settings(global_settings)
115
115
116
116
allocate (global_settings% registry_settings)
117
117
global_settings% registry_settings% url = official_registry_base_url
118
- global_settings% registry_settings% cache_path = join_path(config_path( global_settings), &
118
+ global_settings% registry_settings% cache_path = join_path(global_settings% path_to_config_folder_or_empty( ), &
119
119
& ' dependencies' )
120
- end subroutine use_default_registry_settings
120
+ end
121
121
122
122
! > Read registry settings from the global config file.
123
123
subroutine get_registry_settings (table , global_settings , error )
@@ -155,7 +155,7 @@ subroutine get_registry_settings(table, global_settings, error)
155
155
global_settings% registry_settings% path = path
156
156
else
157
157
! Get canonical, absolute path on both Unix and Windows.
158
- call get_absolute_path(join_path(config_path( global_settings), path), &
158
+ call get_absolute_path(join_path(global_settings% path_to_config_folder_or_empty( ), path), &
159
159
& global_settings% registry_settings% path, error)
160
160
if (allocated (error)) return
161
161
@@ -201,45 +201,44 @@ subroutine get_registry_settings(table, global_settings, error)
201
201
if (.not. exists(cache_path)) call mkdir(cache_path)
202
202
global_settings% registry_settings% cache_path = cache_path
203
203
else
204
- cache_path = join_path(config_path( global_settings), cache_path)
204
+ cache_path = join_path(global_settings% path_to_config_folder_or_empty( ), cache_path)
205
205
if (.not. exists(cache_path)) call mkdir(cache_path)
206
206
! Get canonical, absolute path on both Unix and Windows.
207
207
call get_absolute_path(cache_path, global_settings% registry_settings% cache_path, error)
208
208
if (allocated (error)) return
209
209
end if
210
210
else if (.not. allocated (path)) then
211
- global_settings% registry_settings% cache_path = join_path(config_path(global_settings), &
212
- & ' dependencies' )
211
+ global_settings% registry_settings% cache_path = &
212
+ join_path(global_settings % path_to_config_folder_or_empty(), ' dependencies' )
213
213
end if
214
- end subroutine get_registry_settings
214
+ end
215
215
216
216
! > True if the global config file is not at the default location.
217
- pure logical function has_custom_location(self)
217
+ elemental logical function has_custom_location(self)
218
218
class(fpm_global_settings), intent (in ) :: self
219
219
220
220
has_custom_location = allocated (self% path_to_config_folder) .and. allocated (self% config_file_name)
221
- if (.not. has_custom_location) return
222
- has_custom_location = len_trim (self% path_to_config_folder)> 0 .and. len_trim (self% config_file_name)> 0
223
- end function
221
+ if (.not. has_custom_location) return
222
+ has_custom_location = len_trim (self% path_to_config_folder) > 0 .and. len_trim (self% config_file_name) > 0
223
+ end
224
224
225
225
! > The full path to the global config file.
226
226
function full_path (self ) result(result)
227
227
class(fpm_global_settings), intent (in ) :: self
228
228
character (len= :), allocatable :: result
229
229
230
- result = join_path(config_path( self), self% config_file_name)
231
- end function
230
+ result = join_path(self% path_to_config_folder_or_empty( ), self% config_file_name)
231
+ end
232
232
233
233
! > The path to the global config directory.
234
- function config_path (self )
234
+ pure function path_to_config_folder_or_empty (self )
235
235
class(fpm_global_settings), intent (in ) :: self
236
- character (len= :), allocatable :: config_path
236
+ character (len= :), allocatable :: path_to_config_folder_or_empty
237
237
238
238
if (allocated (self% path_to_config_folder)) then
239
- config_path = self% path_to_config_folder
239
+ path_to_config_folder_or_empty = self% path_to_config_folder
240
240
else
241
- config_path = " "
241
+ path_to_config_folder_or_empty = " "
242
242
end if
243
- end function config_path
244
-
245
- end module fpm_settings
243
+ end
244
+ end
0 commit comments