Skip to content

Commit 15501ea

Browse files
committed
Add: recursive source file discovery
Adds optional recurse option to list_files function
1 parent 35ae709 commit 15501ea

File tree

2 files changed

+48
-4
lines changed

2 files changed

+48
-4
lines changed

fpm/src/fpm_filesystem.f90

Lines changed: 47 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,25 @@ function basename(path,suffix) result (base)
3939
end function basename
4040

4141

42+
logical function is_dir(dir)
43+
character(*), intent(in) :: dir
44+
integer :: stat
45+
46+
select case (get_os_type())
47+
48+
case (OS_LINUX,OS_MACOS)
49+
call execute_command_line("test -d " // dir , exitstat=stat)
50+
51+
case (OS_WINDOWS)
52+
call execute_command_line('cmd /c "if not exist ' // windows_path(dir) // '\ exit /B 1"', exitstat=stat)
53+
54+
end select
55+
56+
is_dir = (stat == 0)
57+
58+
end function is_dir
59+
60+
4261
function join_path(a1,a2,a3,a4,a5) result(path)
4362
! Construct path by joining strings with os file separator
4463
!
@@ -130,12 +149,15 @@ subroutine mkdir(dir)
130149
end subroutine mkdir
131150

132151

133-
subroutine list_files(dir, files)
152+
recursive subroutine list_files(dir, files, recurse)
134153
character(len=*), intent(in) :: dir
135154
type(string_t), allocatable, intent(out) :: files(:)
155+
logical, intent(in), optional :: recurse
136156

137-
integer :: stat, fh
157+
integer :: stat, fh, i
138158
character(:), allocatable :: temp_file
159+
type(string_t), allocatable :: dir_files(:)
160+
type(string_t), allocatable :: sub_dir_files(:)
139161

140162
! Using `inquire` / exists on directories works with gfortran, but not ifort
141163
if (.not. exists(dir)) then
@@ -165,6 +187,29 @@ subroutine list_files(dir, files)
165187
files = read_lines(fh)
166188
close(fh,status="delete")
167189

190+
do i=1,size(files)
191+
files(i)%s = join_path(dir,files(i)%s)
192+
end do
193+
194+
if (present(recurse)) then
195+
if (recurse) then
196+
197+
allocate(sub_dir_files(0))
198+
199+
do i=1,size(files)
200+
if (is_dir(files(i)%s)) then
201+
202+
call list_files(files(i)%s, dir_files, recurse=.true.)
203+
sub_dir_files = [sub_dir_files, dir_files]
204+
205+
end if
206+
end do
207+
208+
files = [files, sub_dir_files]
209+
210+
end if
211+
end if
212+
168213
end subroutine list_files
169214

170215

fpm/src/fpm_sources.f90

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -69,8 +69,7 @@ subroutine add_sources_from_dir(sources,directory,with_executables)
6969
type(srcfile_t), allocatable :: dir_sources(:)
7070

7171
! Scan directory for sources
72-
call list_files(directory, file_names)
73-
file_names = [(string_t(directory//'/'//file_names(j)%s),j=1,size(file_names))]
72+
call list_files(directory, file_names,recurse=.true.)
7473

7574
is_source = [(str_ends_with(lower(file_names(i)%s), ".f90") .or. &
7675
str_ends_with(lower(file_names(i)%s), ".c") .or. &

0 commit comments

Comments
 (0)