Skip to content

Navigation Menu

Sign in
Appearance settings

Search code, repositories, users, issues, pull requests...

Provide feedback

We read every piece of feedback, and take your input very seriously.

Saved searches

Use saved searches to filter your results more quickly

Sign up
Appearance settings

Commit 2bdc50e

Browse files
authored
system: is_directory (#946)
2 parents d5fb3c0 + 8ff26be commit 2bdc50e

File tree

8 files changed

+214
-3
lines changed

8 files changed

+214
-3
lines changed

‎doc/specs/stdlib_system.md‎

Lines changed: 40 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -410,14 +410,52 @@ None.
410410

411411
Returns one of the `integer` `OS_*` parameters representing the OS type, from the `stdlib_system` module, or `OS_UNKNOWN` if undetermined.
412412

413+
### Example
414+
415+
```fortran
416+
{!example/system/example_os_type.f90!}
417+
```
418+
413419
---
414420

421+
## `is_directory` - Test if a path is a directory
422+
423+
### Status
424+
425+
Experimental
426+
427+
### Description
428+
429+
This function checks if a specified file system path is a directory.
430+
It is designed to work across multiple platforms. On Windows, paths with both forward `/` and backward `\` slashes are accepted.
431+
432+
### Syntax
433+
434+
`result = [[stdlib_io(module):is_directory(function)]] (path)`
435+
436+
### Class
437+
438+
Function
439+
440+
### Arguments
441+
442+
`path`: Shall be a character string containing the file system path to evaluate. It is an `intent(in)` argument.
443+
444+
### Return values
445+
446+
The function returns a `logical` value:
447+
448+
- `.true.` if the path matches an existing directory.
449+
- `.false.` otherwise, or if the operating system is unsupported.
450+
415451
### Example
416452

417453
```fortran
418-
{!example/system/example_os_type.f90!}
454+
{!example/system/example_is_directory.f90!}
419455
```
420456

457+
---
458+
421459
## `null_device` - Return the null device file path
422460

423461
### Status
@@ -453,3 +491,4 @@ None.
453491
```fortran
454492
{!example/system/example_null_device.f90!}
455493
```
494+

‎example/system/CMakeLists.txt‎

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
ADD_EXAMPLE(get_runtime_os)
2+
ADD_EXAMPLE(is_directory)
23
ADD_EXAMPLE(null_device)
34
ADD_EXAMPLE(os_type)
45
ADD_EXAMPLE(process_1)
Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
! Demonstrate usage of `is_directory`
2+
program example_is_directory
3+
use stdlib_system, only: is_directory
4+
implicit none
5+
! Test a directory path
6+
if (is_directory("/path/to/check")) then
7+
print *, "The specified path is a directory."
8+
else
9+
print *, "The specified path is not a directory."
10+
end if
11+
end program example_is_directory

‎src/stdlib_system.F90‎

Lines changed: 37 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,8 @@
11
module stdlib_system
22
use, intrinsic :: iso_c_binding, only : c_int, c_long, c_ptr, c_null_ptr, c_int64_t, c_size_t, &
33
c_f_pointer
4-
use stdlib_kinds, only: int64, dp, c_char
4+
use stdlib_kinds, only: int64, dp, c_bool, c_char
5+
use stdlib_strings, only: to_c_char
56
implicit none
67
private
78
public :: sleep
@@ -82,6 +83,22 @@ module stdlib_system
8283
public :: elapsed
8384
public :: is_windows
8485

86+
!! version: experimental
87+
!!
88+
!! Tests if a given path matches an existing directory.
89+
!! ([Specification](../page/specs/stdlib_io.html#is_directory-test-if-a-path-is-a-directory))
90+
!!
91+
!!### Summary
92+
!! Function to evaluate whether a specified path corresponds to an existing directory.
93+
!!
94+
!!### Description
95+
!!
96+
!! This function checks if a given file system path is a directory. It is cross-platform and utilizes
97+
!! native system calls. It supports common operating systems such as Linux, macOS,
98+
!! Windows, and various UNIX-like environments. On unsupported operating systems, the function will return `.false.`.
99+
!!
100+
public :: is_directory
101+
85102
!! version: experimental
86103
!!
87104
!! Returns the file path of the null device, which discards all data written to it.
@@ -636,6 +653,25 @@ pure function OS_NAME(os)
636653
end select
637654
end function OS_NAME
638655

656+
!! Tests if a given path matches an existing directory.
657+
!! Cross-platform implementation without using external C libraries.
658+
logical function is_directory(path)
659+
!> Input path to evaluate
660+
character(*), intent(in) :: path
661+
662+
interface
663+
664+
logical(c_bool) function stdlib_is_directory(path) bind(c, name="stdlib_is_directory")
665+
import c_bool, c_char
666+
character(kind=c_char), intent(in) :: path(*)
667+
end function stdlib_is_directory
668+
669+
end interface
670+
671+
is_directory = logical(stdlib_is_directory(to_c_char(trim(path))))
672+
673+
end function is_directory
674+
639675
!> Returns the file path of the null device for the current operating system.
640676
!>
641677
!> Version: Helper function.

‎src/stdlib_system_subprocess.F90‎

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
submodule (stdlib_system) stdlib_system_subprocess
22
use iso_c_binding
33
use iso_fortran_env, only: int64, real64
4-
use stdlib_strings, only: to_c_char, join
4+
use stdlib_strings, only: join
55
use stdlib_linalg_state, only: linalg_state_type, LINALG_ERROR, linalg_error_handling
66
implicit none(type, external)
77

‎src/stdlib_system_subprocess.c‎

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@
1010
#else
1111
#define _POSIX_C_SOURCE 199309L
1212
#include <sys/wait.h>
13+
#include <sys/stat.h>
1314
#include <unistd.h>
1415
#include <time.h>
1516
#include <errno.h>
@@ -220,6 +221,12 @@ bool process_kill_windows(stdlib_pid pid) {
220221
return true;
221222
}
222223

224+
// Check if input path is a directory
225+
bool stdlib_is_directory_windows(const char *path) {
226+
DWORD attrs = GetFileAttributesA(path);
227+
return (attrs != INVALID_FILE_ATTRIBUTES) // Path exists
228+
&& (attrs & FILE_ATTRIBUTE_DIRECTORY); // Path is a directory
229+
}
223230

224231
#else // _WIN32
225232

@@ -292,12 +299,29 @@ void process_create_posix(stdlib_pid* pid)
292299
(*pid) = (stdlib_pid) fork();
293300
}
294301

302+
// On UNIX systems: check if input path is a directory
303+
bool stdlib_is_directory_posix(const char *path) {
304+
struct stat sb;
305+
return stat(path, &sb) == 0 && S_ISDIR(sb.st_mode);
306+
}
307+
295308
#endif // _WIN32
296309

297310
/////////////////////////////////////////////////////////////////////////////////////
298311
// Cross-platform interface
299312
/////////////////////////////////////////////////////////////////////////////////////
300313

314+
// Cross-platform interface: query directory state
315+
bool stdlib_is_directory(const char *path) {
316+
// Invalid input
317+
if (path == NULL || strlen(path) == 0) return false;
318+
#ifdef _WIN32
319+
return stdlib_is_directory_windows(path);
320+
#else
321+
return stdlib_is_directory_posix(path);
322+
#endif // _WIN32
323+
}
324+
301325
// Create or fork process
302326
void process_create(const char* cmd, const char* stdin_stream, const char* stdin_file,
303327
const char* stdout_file, const char* stderr_file,

‎test/system/CMakeLists.txt‎

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
ADDTEST(filesystem)
12
ADDTEST(os)
23
ADDTEST(sleep)
34
ADDTEST(subprocess)

‎test/system/test_filesystem.f90‎

Lines changed: 99 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,99 @@
1+
module test_filesystem
2+
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
3+
use stdlib_system, only: is_directory
4+
5+
implicit none
6+
7+
contains
8+
9+
!> Collect all exported unit tests
10+
subroutine collect_suite(testsuite)
11+
!> Collection of tests
12+
type(unittest_type), allocatable, intent(out) :: testsuite(:)
13+
14+
testsuite = [ &
15+
new_unittest("fs_is_directory_dir", test_is_directory_dir), &
16+
new_unittest("fs_is_directory_file", test_is_directory_file) &
17+
]
18+
end subroutine collect_suite
19+
20+
! Test `is_directory` for a directory
21+
subroutine test_is_directory_dir(error)
22+
type(error_type), allocatable, intent(out) :: error
23+
character(len=256) :: dirname
24+
integer :: ios, iocmd
25+
character(len=512) :: msg
26+
27+
dirname = "this_test_dir_tmp"
28+
29+
! Create a directory
30+
call execute_command_line("mkdir " // dirname, exitstat=ios, cmdstat=iocmd, cmdmsg=msg)
31+
call check(error, ios == 0 .and. iocmd == 0, "Cannot create test directory: " // trim(msg))
32+
if (allocated(error)) return
33+
34+
! Verify `is_directory` identifies it as a directory
35+
call check(error, is_directory(dirname), "is_directory did not recognize a valid directory")
36+
if (allocated(error)) return
37+
38+
! Clean up: remove the directory
39+
call execute_command_line("rmdir " // dirname, exitstat=ios, cmdstat=iocmd, cmdmsg=msg)
40+
call check(error, ios == 0 .and. iocmd == 0, "Cannot remove test directory: " // trim(msg))
41+
end subroutine test_is_directory_dir
42+
43+
! Test `is_directory` for a regular file
44+
subroutine test_is_directory_file(error)
45+
type(error_type), allocatable, intent(out) :: error
46+
character(len=256) :: filename
47+
logical :: result
48+
integer :: ios, iunit
49+
character(len=512) :: msg
50+
51+
filename = "test_file.txt"
52+
53+
! Create a file
54+
open(newunit=iunit, file=filename, status="replace", iostat=ios, iomsg=msg)
55+
call check(error, ios == 0, "Cannot create test file: " // trim(msg))
56+
if (allocated(error)) return
57+
58+
! Verify `is_directory` identifies it as not a directory
59+
result = is_directory(filename)
60+
call check(error, .not. result, "is_directory falsely recognized a regular file as a directory")
61+
if (allocated(error)) return
62+
63+
! Clean up: remove the file
64+
close(iunit,status='delete',iostat=ios,iomsg=msg)
65+
call check(error, ios == 0, "Cannot delete test file: " // trim(msg))
66+
if (allocated(error)) return
67+
68+
end subroutine test_is_directory_file
69+
70+
71+
end module test_filesystem
72+
73+
program tester
74+
use, intrinsic :: iso_fortran_env, only : error_unit
75+
use testdrive, only : run_testsuite, new_testsuite, testsuite_type
76+
use test_filesystem, only : collect_suite
77+
78+
implicit none
79+
80+
integer :: stat, is
81+
type(testsuite_type), allocatable :: testsuites(:)
82+
character(len=*), parameter :: fmt = '("#", *(1x, a))'
83+
84+
stat = 0
85+
86+
testsuites = [ &
87+
new_testsuite("filesystem", collect_suite) &
88+
]
89+
90+
do is = 1, size(testsuites)
91+
write(error_unit, fmt) "Testing:", testsuites(is)%name
92+
call run_testsuite(testsuites(is)%collect, error_unit, stat)
93+
end do
94+
95+
if (stat > 0) then
96+
write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
97+
error stop
98+
end if
99+
end program

0 commit comments

Comments
(0)

AltStyle によって変換されたページ (->オリジナル) /