Skip to content

Commit c1830df

Browse files
committed
Add is_windows and test it
1 parent 96593b5 commit c1830df

File tree

2 files changed

+37
-1
lines changed

2 files changed

+37
-1
lines changed

src/stdlib_io_filesystem.F90

Lines changed: 22 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,13 +6,34 @@ module stdlib_io_filesystem
66
implicit none
77
private
88

9-
public :: exists, list_dir, run, temp_dir
9+
public :: temp_dir, is_windows, exists, list_dir, run
1010

1111
character(*), parameter :: temp_dir = 'temp'
1212
character(*), parameter :: listed_contents = temp_dir//'/listed_contents.txt'
1313

1414
contains
1515

16+
!> Version: experimental
17+
!>
18+
!> Whether the operating system is Windows.
19+
!> [Specification](../page/specs/stdlib_io.html#is_windows)
20+
logical function is_windows()
21+
character(len=255) :: value
22+
integer :: length, stat
23+
24+
call get_environment_variable('OSTYPE', value, length, stat)
25+
if (stat == 0 .and. length > 0 .and. (index(value, 'win') > 0 .or. index(value, 'msys') > 0)) then
26+
is_windows = .true.; return
27+
end if
28+
29+
call get_environment_variable('OS', value, length, stat)
30+
if (stat == 0 .and. length > 0 .and. index(value, 'Windows_NT') > 0) then
31+
is_windows = .true.; return
32+
end if
33+
34+
is_windows = .false.
35+
end
36+
1637
!> Version: experimental
1738
!>
1839
!> Whether a file or directory exists at the given path.

test/io/test_filesystem.f90

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ subroutine collect_filesystem(testsuite)
1717
type(unittest_type), allocatable, intent(out) :: testsuite(:)
1818

1919
testsuite = [ &
20+
new_unittest("fs_file_is_windows", fs_is_windows), &
2021
new_unittest("fs_file_not_exists", fs_file_not_exists, should_fail=.true.), &
2122
new_unittest("fs_file_exists", fs_file_exists), &
2223
new_unittest("fs_current_dir_exists", fs_current_dir_exists), &
@@ -30,6 +31,20 @@ subroutine collect_filesystem(testsuite)
3031
]
3132
end
3233

34+
subroutine fs_is_windows(error)
35+
type(error_type), allocatable, intent(out) :: error
36+
37+
character(len=255) :: value
38+
integer :: length, stat
39+
40+
call get_environment_variable('HOMEDRIVE', value, length, stat)
41+
if (is_windows()) then
42+
call check(error, stat == 0 .and. length > 0, "Windows should be detected.")
43+
else
44+
call check(error, stat /= 0 .and. length == 0, "Windows should not be detected.")
45+
end if
46+
end
47+
3348
subroutine fs_file_not_exists(error)
3449
type(error_type), allocatable, intent(out) :: error
3550

0 commit comments

Comments
 (0)