aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm_filesystem.f9049
-rw-r--r--fpm/src/fpm_sources.f903
2 files changed, 48 insertions, 4 deletions
diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90
index 297278b..d035e31 100644
--- a/fpm/src/fpm_filesystem.f90
+++ b/fpm/src/fpm_filesystem.f90
@@ -39,6 +39,25 @@ function basename(path,suffix) result (base)
end function basename
+logical function is_dir(dir)
+ character(*), intent(in) :: dir
+ integer :: stat
+
+ select case (get_os_type())
+
+ case (OS_LINUX,OS_MACOS)
+ call execute_command_line("test -d " // dir , exitstat=stat)
+
+ case (OS_WINDOWS)
+ call execute_command_line('cmd /c "if not exist ' // windows_path(dir) // '\ exit /B 1"', exitstat=stat)
+
+ end select
+
+ is_dir = (stat == 0)
+
+end function is_dir
+
+
function join_path(a1,a2,a3,a4,a5) result(path)
! Construct path by joining strings with os file separator
!
@@ -130,12 +149,15 @@ subroutine mkdir(dir)
end subroutine mkdir
-subroutine list_files(dir, files)
+recursive subroutine list_files(dir, files, recurse)
character(len=*), intent(in) :: dir
type(string_t), allocatable, intent(out) :: files(:)
+ logical, intent(in), optional :: recurse
- integer :: stat, fh
+ integer :: stat, fh, i
character(:), allocatable :: temp_file
+ type(string_t), allocatable :: dir_files(:)
+ type(string_t), allocatable :: sub_dir_files(:)
! Using `inquire` / exists on directories works with gfortran, but not ifort
if (.not. exists(dir)) then
@@ -165,6 +187,29 @@ subroutine list_files(dir, files)
files = read_lines(fh)
close(fh,status="delete")
+ do i=1,size(files)
+ files(i)%s = join_path(dir,files(i)%s)
+ end do
+
+ if (present(recurse)) then
+ if (recurse) then
+
+ allocate(sub_dir_files(0))
+
+ do i=1,size(files)
+ if (is_dir(files(i)%s)) then
+
+ call list_files(files(i)%s, dir_files, recurse=.true.)
+ sub_dir_files = [sub_dir_files, dir_files]
+
+ end if
+ end do
+
+ files = [files, sub_dir_files]
+
+ end if
+ end if
+
end subroutine list_files
diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90
index fb6e57a..fb02758 100644
--- a/fpm/src/fpm_sources.f90
+++ b/fpm/src/fpm_sources.f90
@@ -69,8 +69,7 @@ subroutine add_sources_from_dir(sources,directory,with_executables)
type(srcfile_t), allocatable :: dir_sources(:)
! Scan directory for sources
- call list_files(directory, file_names)
- file_names = [(string_t(directory//'/'//file_names(j)%s),j=1,size(file_names))]
+ call list_files(directory, file_names,recurse=.true.)
is_source = [(str_ends_with(lower(file_names(i)%s), ".f90") .or. &
str_ends_with(lower(file_names(i)%s), ".c") .or. &