Skip to content

Commit 8ffe495

Browse files
authored
Merge pull request #507 from brocolis/file-listing
optimize file listing
2 parents 9e26b2d + 18e2dab commit 8ffe495

File tree

4 files changed

+232
-6
lines changed

4 files changed

+232
-6
lines changed

src/filesystem_utilities.c

Lines changed: 41 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,41 @@
1+
#include <sys/stat.h>
2+
#include <dirent.h>
3+
4+
#ifdef __APPLE__
5+
DIR * opendir$INODE64( const char * dirName );
6+
struct dirent * readdir$INODE64( DIR * dir );
7+
#endif
8+
9+
int c_is_dir(const char *path)
10+
{
11+
struct stat m;
12+
int r = stat(path, &m);
13+
return r == 0 && S_ISDIR(m.st_mode);
14+
}
15+
16+
const char *get_d_name(struct dirent *d)
17+
{
18+
return (const char *) d->d_name;
19+
}
20+
21+
22+
23+
DIR *c_opendir(const char *dirname){
24+
25+
#ifdef __APPLE__
26+
return opendir$INODE64(dirname);
27+
#else
28+
return opendir(dirname);
29+
#endif
30+
31+
}
32+
33+
struct dirent *c_readdir(DIR *dirp){
34+
35+
#ifdef __APPLE__
36+
return readdir$INODE64(dirp);
37+
#else
38+
return readdir(dirp);
39+
#endif
40+
41+
}

src/fpm_environment.f90

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -40,14 +40,24 @@ integer function get_os_type() result(r)
4040
character(len=32) :: val
4141
integer :: length, rc
4242
logical :: file_exists
43+
logical, save :: first_run = .true.
44+
integer, save :: ret = OS_UNKNOWN
45+
!omp threadprivate(ret, first_run)
4346

47+
if (.not. first_run) then
48+
r = ret
49+
return
50+
end if
51+
52+
first_run = .false.
4453
r = OS_UNKNOWN
4554

4655
! Check environment variable `OS`.
4756
call get_environment_variable('OS', val, length, rc)
4857

4958
if (rc == 0 .and. length > 0 .and. index(val, 'Windows_NT') > 0) then
5059
r = OS_WINDOWS
60+
ret = r
5161
return
5262
end if
5363

@@ -58,42 +68,49 @@ integer function get_os_type() result(r)
5868
! Linux
5969
if (index(val, 'linux') > 0) then
6070
r = OS_LINUX
71+
ret = r
6172
return
6273
end if
6374

6475
! macOS
6576
if (index(val, 'darwin') > 0) then
6677
r = OS_MACOS
78+
ret = r
6779
return
6880
end if
6981

7082
! Windows, MSYS, MinGW, Git Bash
7183
if (index(val, 'win') > 0 .or. index(val, 'msys') > 0) then
7284
r = OS_WINDOWS
85+
ret = r
7386
return
7487
end if
7588

7689
! Cygwin
7790
if (index(val, 'cygwin') > 0) then
7891
r = OS_CYGWIN
92+
ret = r
7993
return
8094
end if
8195

8296
! Solaris, OpenIndiana, ...
8397
if (index(val, 'SunOS') > 0 .or. index(val, 'solaris') > 0) then
8498
r = OS_SOLARIS
99+
ret = r
85100
return
86101
end if
87102

88103
! FreeBSD
89104
if (index(val, 'FreeBSD') > 0 .or. index(val, 'freebsd') > 0) then
90105
r = OS_FREEBSD
106+
ret = r
91107
return
92108
end if
93109

94110
! OpenBSD
95111
if (index(val, 'OpenBSD') > 0 .or. index(val, 'openbsd') > 0) then
96112
r = OS_OPENBSD
113+
ret = r
97114
return
98115
end if
99116
end if
@@ -103,6 +120,7 @@ integer function get_os_type() result(r)
103120

104121
if (file_exists) then
105122
r = OS_LINUX
123+
ret = r
106124
return
107125
end if
108126

@@ -111,6 +129,7 @@ integer function get_os_type() result(r)
111129

112130
if (file_exists) then
113131
r = OS_MACOS
132+
ret = r
114133
return
115134
end if
116135

@@ -119,6 +138,7 @@ integer function get_os_type() result(r)
119138

120139
if (file_exists) then
121140
r = OS_FREEBSD
141+
ret = r
122142
return
123143
end if
124144
end function get_os_type

src/fpm_filesystem.f90 renamed to src/fpm_filesystem.F90

Lines changed: 139 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ module fpm_filesystem
77
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
88
use fpm_environment, only: separator, get_env
99
use fpm_strings, only: f_string, replace, string_t, split
10+
use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer
1011
use fpm_error, only : fpm_stop
1112
implicit none
1213
private
@@ -17,6 +18,39 @@ module fpm_filesystem
1718

1819
integer, parameter :: LINE_BUFFER_LEN = 1000
1920

21+
#ifndef FPM_BOOTSTRAP
22+
interface
23+
function c_opendir(dir) result(r) bind(c, name="c_opendir")
24+
import c_char, c_ptr
25+
character(kind=c_char), intent(in) :: dir(*)
26+
type(c_ptr) :: r
27+
end function c_opendir
28+
29+
function c_readdir(dir) result(r) bind(c, name="c_readdir")
30+
import c_ptr
31+
type(c_ptr), intent(in), value :: dir
32+
type(c_ptr) :: r
33+
end function c_readdir
34+
35+
function c_closedir(dir) result(r) bind(c, name="closedir")
36+
import c_ptr, c_int
37+
type(c_ptr), intent(in), value :: dir
38+
integer(kind=c_int) :: r
39+
end function c_closedir
40+
41+
function c_get_d_name(dir) result(r) bind(c, name="get_d_name")
42+
import c_ptr
43+
type(c_ptr), intent(in), value :: dir
44+
type(c_ptr) :: r
45+
end function c_get_d_name
46+
47+
function c_is_dir(path) result(r) bind(c, name="c_is_dir")
48+
import c_char, c_int
49+
character(kind=c_char), intent(in) :: path(*)
50+
integer(kind=c_int) :: r
51+
end function c_is_dir
52+
end interface
53+
#endif
2054

2155
contains
2256

@@ -226,13 +260,23 @@ function join_path(a1,a2,a3,a4,a5) result(path)
226260
character(len=*), intent(in), optional :: a3, a4, a5
227261
character(len=:), allocatable :: path
228262
character(len=1) :: filesep
263+
logical, save :: has_cache = .false.
264+
character(len=1), save :: cache = '/'
265+
!$omp threadprivate(has_cache, cache)
229266

230-
select case (get_os_type())
231-
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
232-
filesep = '/'
233-
case (OS_WINDOWS)
234-
filesep = '\'
235-
end select
267+
if (has_cache) then
268+
filesep = cache
269+
else
270+
select case (get_os_type())
271+
case default
272+
filesep = '/'
273+
case (OS_WINDOWS)
274+
filesep = '\'
275+
end select
276+
277+
cache = filesep
278+
has_cache = .true.
279+
end if
236280

237281
path = a1 // filesep // a2
238282

@@ -311,7 +355,94 @@ subroutine mkdir(dir)
311355
end if
312356
end subroutine mkdir
313357

358+
#ifndef FPM_BOOTSTRAP
359+
!> Get file & directory names in directory `dir` using iso_c_binding.
360+
!!
361+
!! - File/directory names return are relative to cwd, ie. preprended with `dir`
362+
!! - Includes files starting with `.` except current directory and parent directory
363+
!!
364+
recursive subroutine list_files(dir, files, recurse)
365+
character(len=*), intent(in) :: dir
366+
type(string_t), allocatable, intent(out) :: files(:)
367+
logical, intent(in), optional :: recurse
368+
369+
integer :: i
370+
type(string_t), allocatable :: dir_files(:)
371+
type(string_t), allocatable :: sub_dir_files(:)
372+
373+
type(c_ptr) :: dir_handle
374+
type(c_ptr) :: dir_entry_c
375+
character(len=:,kind=c_char), allocatable :: fortran_name
376+
character(len=:), allocatable :: string_fortran
377+
integer, parameter :: N_MAX = 256
378+
type(string_t) :: files_tmp(N_MAX)
379+
integer(kind=c_int) :: r
380+
381+
if (c_is_dir(dir(1:len_trim(dir))//c_null_char) .eq. 0) then
382+
allocate (files(0))
383+
return
384+
end if
385+
386+
dir_handle = c_opendir(dir(1:len_trim(dir))//c_null_char)
387+
if (.not. c_associated(dir_handle)) then
388+
print *, 'c_opendir() failed'
389+
error stop
390+
end if
391+
392+
i = 0
393+
allocate(files(0))
314394

395+
do
396+
dir_entry_c = c_readdir(dir_handle)
397+
if (.not. c_associated(dir_entry_c)) then
398+
exit
399+
else
400+
string_fortran = f_string(c_get_d_name(dir_entry_c))
401+
402+
if ((string_fortran .eq. '.' .or. string_fortran .eq. '..')) then
403+
cycle
404+
end if
405+
406+
i = i + 1
407+
408+
if (i .gt. N_MAX) then
409+
files = [files, files_tmp]
410+
i = 1
411+
end if
412+
413+
files_tmp(i)%s = join_path(dir, string_fortran)
414+
end if
415+
end do
416+
417+
r = c_closedir(dir_handle)
418+
419+
if (r .ne. 0) then
420+
print *, 'c_closedir() failed'
421+
error stop
422+
end if
423+
424+
if (i .gt. 0) then
425+
files = [files, files_tmp(1:i)]
426+
end if
427+
428+
if (present(recurse)) then
429+
if (recurse) then
430+
431+
allocate(sub_dir_files(0))
432+
433+
do i=1,size(files)
434+
if (c_is_dir(files(i)%s//c_null_char) .ne. 0) then
435+
call list_files(files(i)%s, dir_files, recurse=.true.)
436+
sub_dir_files = [sub_dir_files, dir_files]
437+
end if
438+
end do
439+
440+
files = [files, sub_dir_files]
441+
end if
442+
end if
443+
end subroutine list_files
444+
445+
#else
315446
!> Get file & directory names in directory `dir`.
316447
!!
317448
!! - File/directory names return are relative to cwd, ie. preprended with `dir`
@@ -376,6 +507,8 @@ recursive subroutine list_files(dir, files, recurse)
376507

377508
end subroutine list_files
378509

510+
#endif
511+
379512

380513
!> test if pathname already exists
381514
logical function exists(filename) result(r)

src/fpm_strings.f90

Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,7 @@
3131

3232
module fpm_strings
3333
use iso_fortran_env, only: int64
34+
use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer, c_size_t
3435
implicit none
3536

3637
private
@@ -73,6 +74,10 @@ module fpm_strings
7374
module procedure new_string_t
7475
end interface string_t
7576

77+
interface f_string
78+
module procedure f_string, f_string_cptr, f_string_cptr_n
79+
end interface f_string
80+
7681
contains
7782

7883
!> test if a CHARACTER string ends with a specified suffix
@@ -128,6 +133,33 @@ function f_string(c_string)
128133
end function f_string
129134

130135

136+
!> return Fortran character variable when given a null-terminated c_ptr
137+
function f_string_cptr(cptr) result(s)
138+
type(c_ptr), intent(in), value :: cptr
139+
character(len=:,kind=c_char), allocatable :: s
140+
141+
interface
142+
function c_strlen(s) result(r) bind(c, name="strlen")
143+
import c_size_t, c_ptr
144+
type(c_ptr), intent(in), value :: s
145+
integer(kind=c_size_t) :: r
146+
end function
147+
end interface
148+
149+
s = f_string_cptr_n(cptr, c_strlen(cptr))
150+
end function
151+
152+
!> return Fortran character variable when given a null-terminated c_ptr and its length
153+
function f_string_cptr_n(cptr, n) result(s)
154+
type(c_ptr), intent(in), value :: cptr
155+
integer(kind=c_size_t), intent(in) :: n
156+
character(len=n,kind=c_char) :: s
157+
character(len=n,kind=c_char), pointer :: sptr
158+
159+
call c_f_pointer(cptr, sptr)
160+
s = sptr
161+
end function
162+
131163
!> Hash a character(*) string of default kind
132164
pure function fnv_1a_char(input, seed) result(hash)
133165
character(*), intent(in) :: input

0 commit comments

Comments
 (0)