Skip to content

Commit e70422f

Browse files
authored
Merge pull request #946 from fortran-lang/just-refactorings
Just some refactoring
2 parents f4d9222 + b937d64 commit e70422f

File tree

5 files changed

+76
-80
lines changed

5 files changed

+76
-80
lines changed

src/fpm.f90

Lines changed: 17 additions & 18 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
@@ -324,7 +323,7 @@ end subroutine check_modules_for_duplicates
324323
subroutine check_module_names(model, error)
325324
type(fpm_model_t), intent(in) :: model
326325
type(error_t), allocatable, intent(out) :: error
327-
integer :: i,j,k,l,m
326+
integer :: k,l,m
328327
logical :: valid,errors_found,enforce_this_file
329328
type(string_t) :: package_name,module_name,package_prefix
330329

@@ -617,29 +616,29 @@ subroutine cmd_run(settings,test)
617616
call fpm_stop(stat(firsterror),'*cmd_run*:stopping due to failed executions')
618617
end if
619618

620-
endif
619+
end if
620+
621621
contains
622+
622623
subroutine compact_list_all()
623624
integer, parameter :: LINE_WIDTH = 80
624-
integer :: i, j, nCol
625-
j = 1
625+
integer :: ii, jj, nCol
626+
jj = 1
626627
nCol = LINE_WIDTH/col_width
627628
write(stderr,*) 'Available names:'
628-
do i=1,size(targets)
629+
do ii=1,size(targets)
629630

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

632633
if (exe_target%target_type == FPM_TARGET_EXECUTABLE .and. &
633634
allocated(exe_target%dependencies)) then
634635

635636
exe_source => exe_target%dependencies(1)%ptr%source
636637

637638
if (exe_source%unit_scope == run_scope) then
638-
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
642-
641+
jj = jj + 1
643642
end if
644643
end if
645644
end do
@@ -648,15 +647,15 @@ end subroutine compact_list_all
648647

649648
subroutine compact_list()
650649
integer, parameter :: LINE_WIDTH = 80
651-
integer :: i, j, nCol
652-
j = 1
650+
integer :: ii, jj, nCol
651+
jj = 1
653652
nCol = LINE_WIDTH/col_width
654653
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
659-
enddo
654+
do ii=1,size(executables)
655+
write(stderr,'(A)',advance=(merge("yes","no ",modulo(jj,nCol)==0))) &
656+
& [character(len=col_width) :: basename(executables(ii)%s, suffix=.false.)]
657+
jj = jj + 1
658+
end do
660659
write(stderr,*)
661660
end subroutine compact_list
662661

src/fpm/cmd/update.f90

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -24,15 +24,13 @@ 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

3735
call new_dependency_tree(deps, cache=cache, &
3836
verbosity=merge(2, 1, settings%verbose))

src/fpm/dependency.f90

Lines changed: 27 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -123,7 +123,9 @@ module fpm_dependency
123123
type(dependency_node_t), allocatable :: dep(:)
124124
!> Cache file
125125
character(len=:), allocatable :: cache
126+
126127
contains
128+
127129
!> Overload procedure to add new dependencies to the tree
128130
generic :: add => add_project, add_project_dependencies, add_dependencies, &
129131
add_dependency, add_dependency_node
@@ -194,13 +196,9 @@ subroutine new_dependency_tree(self, verbosity, cache)
194196
call resize(self%dep)
195197
self%dep_dir = join_path("build", "dependencies")
196198

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

201-
if (present(cache)) then
202-
self%cache = cache
203-
end if
201+
if (present(cache)) self%cache = cache
204202

205203
end subroutine new_dependency_tree
206204

@@ -311,15 +309,15 @@ subroutine add_project(self, package, error)
311309

312310
! After resolving all dependencies, check if we have cached ones to avoid updates
313311
if (allocated(self%cache)) then
314-
call new_dependency_tree(cached, verbosity=self%verbosity,cache=self%cache)
312+
call new_dependency_tree(cached, verbosity=self%verbosity, cache=self%cache)
315313
call cached%load(self%cache, error)
316314
if (allocated(error)) return
317315

318316
! 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
317+
do id = 2, cached%ndep
318+
cached%dep(id)%cached = .true.
319+
call self%add(cached%dep(id), error)
320+
if (allocated(error)) return
323321
end do
324322
end if
325323

@@ -443,13 +441,13 @@ subroutine add_dependency_node(self, dependency, error)
443441
! the manifest has priority
444442
if (dependency%cached) then
445443
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.
444+
if (self%verbosity > 0) write (self%unit, out_fmt) "Dependency change detected:", dependency%name
445+
self%dep(id)%update = .true.
448446
else
449-
! Store the cached one
450-
self%dep(id) = dependency
451-
self%dep(id)%update = .false.
452-
endif
447+
! Store the cached one
448+
self%dep(id) = dependency
449+
self%dep(id)%update = .false.
450+
end if
453451
end if
454452
else
455453
! New dependency: add from scratch
@@ -498,7 +496,7 @@ subroutine update_dependency(self, name, error)
498496

499497
associate (dep => self%dep(id))
500498
if (allocated(dep%git) .and. dep%update) then
501-
if (self%verbosity>0) write (self%unit, out_fmt) "Update:", dep%name
499+
if (self%verbosity > 0) write (self%unit, out_fmt) "Update:", dep%name
502500
proj_dir = join_path(self%dep_dir, dep%name)
503501
call dep%git%checkout(proj_dir, error)
504502
if (allocated(error)) return
@@ -722,7 +720,7 @@ subroutine check_and_read_pkg_data(json, node, download_url, version, error)
722720
character(:), allocatable :: version_key, version_str, error_message, namespace, name
723721

724722
namespace = ""
725-
name = "UNNAMED_NODE"
723+
name = "UNNAMED_NODE"
726724
if (allocated(node%namespace)) namespace = node%namespace
727725
if (allocated(node%name)) name = node%name
728726

@@ -1199,27 +1197,27 @@ logical function dependency_has_changed(cached, manifest, verbosity, iunit) resu
11991197
!> may not have it
12001198
if (allocated(cached%version) .and. allocated(manifest%version)) then
12011199
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
1200+
if (verbosity > 1) write (iunit, out_fmt) "VERSION has changed: "//cached%version%s()//" vs. "//manifest%version%s()
1201+
return
1202+
end if
12051203
else
1206-
if (verbosity>1) write(iunit,out_fmt) "VERSION has changed presence "
1204+
if (verbosity > 1) write (iunit, out_fmt) "VERSION has changed presence "
12071205
end if
12081206
if (allocated(cached%revision) .and. allocated(manifest%revision)) then
12091207
if (cached%revision /= manifest%revision) then
1210-
if (verbosity>1) write(iunit,out_fmt) "REVISION has changed: "//cached%revision//" vs. "//manifest%revision
1208+
if (verbosity > 1) write (iunit, out_fmt) "REVISION has changed: "//cached%revision//" vs. "//manifest%revision
12111209
return
1212-
endif
1210+
end if
12131211
else
1214-
if (verbosity>1) write(iunit,out_fmt) "REVISION has changed presence "
1212+
if (verbosity > 1) write (iunit, out_fmt) "REVISION has changed presence "
12151213
end if
12161214
if (allocated(cached%proj_dir) .and. allocated(manifest%proj_dir)) then
12171215
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
1216+
if (verbosity > 1) write (iunit, out_fmt) "PROJECT DIR has changed: "//cached%proj_dir//" vs. "//manifest%proj_dir
12191217
return
1220-
endif
1218+
end if
12211219
else
1222-
if (verbosity>1) write(iunit,out_fmt) "PROJECT DIR has changed presence "
1220+
if (verbosity > 1) write (iunit, out_fmt) "PROJECT DIR has changed presence "
12231221
end if
12241222

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

src/fpm_filesystem.F90

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,9 @@ subroutine env_variable(var, name)
7676
end subroutine env_variable
7777

7878

79-
!> Extract filename from path with/without suffix
79+
!> Extract filename from path with or without suffix.
80+
!>
81+
!> The suffix is included by default.
8082
function basename(path,suffix) result (base)
8183

8284
character(*), intent(In) :: path

src/fpm_settings.f90

Lines changed: 27 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -4,13 +4,14 @@ module fpm_settings
44
use fpm_environment, only: os_is_unix
55
use fpm_error, only: error_t, fatal_error
66
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+
99
implicit none
1010
private
1111
public :: fpm_global_settings, get_global_settings, get_registry_settings, official_registry_base_url
1212

1313
character(*), parameter :: official_registry_base_url = 'https://registry-apis.vercel.app'
14+
character(*), parameter :: default_config_file_name = 'config.toml'
1415

1516
type :: fpm_global_settings
1617
!> Path to the global config file excluding the file name.
@@ -20,7 +21,7 @@ module fpm_settings
2021
!> Registry configs.
2122
type(fpm_registry_settings), allocatable :: registry_settings
2223
contains
23-
procedure :: has_custom_location, full_path
24+
procedure :: has_custom_location, full_path, path_to_config_folder_or_empty
2425
end type
2526

2627
type :: fpm_registry_settings
@@ -56,8 +57,8 @@ subroutine get_global_settings(global_settings, error)
5657
! Use custom path to the config file if it was specified.
5758
if (global_settings%has_custom_location()) then
5859
! 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
6162
end if
6263

6364
! Throw error if the file doesn't exist.
@@ -77,7 +78,7 @@ subroutine get_global_settings(global_settings, error)
7778
end if
7879

7980
! Use default file name.
80-
global_settings%config_file_name = 'config.toml'
81+
global_settings%config_file_name = default_config_file_name
8182

8283
! Apply default registry settings and return if config file doesn't exist.
8384
if (.not. exists(global_settings%full_path())) then
@@ -105,8 +106,7 @@ subroutine get_global_settings(global_settings, error)
105106
else
106107
call use_default_registry_settings(global_settings)
107108
end if
108-
109-
end subroutine get_global_settings
109+
end
110110

111111
!> Default registry settings are typically applied if the config file doesn't exist or no registry table was found in
112112
!> the global config file.
@@ -115,9 +115,9 @@ subroutine use_default_registry_settings(global_settings)
115115

116116
allocate (global_settings%registry_settings)
117117
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(), &
119119
& 'dependencies')
120-
end subroutine use_default_registry_settings
120+
end
121121

122122
!> Read registry settings from the global config file.
123123
subroutine get_registry_settings(table, global_settings, error)
@@ -155,7 +155,7 @@ subroutine get_registry_settings(table, global_settings, error)
155155
global_settings%registry_settings%path = path
156156
else
157157
! 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), &
159159
& global_settings%registry_settings%path, error)
160160
if (allocated(error)) return
161161

@@ -201,45 +201,44 @@ subroutine get_registry_settings(table, global_settings, error)
201201
if (.not. exists(cache_path)) call mkdir(cache_path)
202202
global_settings%registry_settings%cache_path = cache_path
203203
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)
205205
if (.not. exists(cache_path)) call mkdir(cache_path)
206206
! Get canonical, absolute path on both Unix and Windows.
207207
call get_absolute_path(cache_path, global_settings%registry_settings%cache_path, error)
208208
if (allocated(error)) return
209209
end if
210210
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')
213213
end if
214-
end subroutine get_registry_settings
214+
end
215215

216216
!> 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)
218218
class(fpm_global_settings), intent(in) :: self
219219

220220
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
224224

225225
!> The full path to the global config file.
226226
function full_path(self) result(result)
227227
class(fpm_global_settings), intent(in) :: self
228228
character(len=:), allocatable :: result
229229

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
232232

233233
!> The path to the global config directory.
234-
function config_path(self)
234+
pure function path_to_config_folder_or_empty(self)
235235
class(fpm_global_settings), intent(in) :: self
236-
character(len=:), allocatable :: config_path
236+
character(len=:), allocatable :: path_to_config_folder_or_empty
237237

238238
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
240240
else
241-
config_path = ""
241+
path_to_config_folder_or_empty = ""
242242
end if
243-
end function config_path
244-
245-
end module fpm_settings
243+
end
244+
end

0 commit comments

Comments
 (0)