Skip to content

Commit

Permalink
Add is_windows and test it
Browse files Browse the repository at this point in the history
  • Loading branch information
minhqdao committed Sep 20, 2024
1 parent 96593b5 commit c1830df
Show file tree
Hide file tree
Showing 2 changed files with 37 additions and 1 deletion.
23 changes: 22 additions & 1 deletion src/stdlib_io_filesystem.F90
Original file line number Diff line number Diff line change
Expand Up @@ -6,13 +6,34 @@ module stdlib_io_filesystem
implicit none
private

public :: exists, list_dir, run, temp_dir
public :: temp_dir, is_windows, exists, list_dir, run

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

contains

!> Version: experimental
!>
!> Whether the operating system is Windows.
!> [Specification](../page/specs/stdlib_io.html#is_windows)
logical function is_windows()
character(len=255) :: value
integer :: length, stat

call get_environment_variable('OSTYPE', value, length, stat)
if (stat == 0 .and. length > 0 .and. (index(value, 'win') > 0 .or. index(value, 'msys') > 0)) then
is_windows = .true.; return
end if

call get_environment_variable('OS', value, length, stat)
if (stat == 0 .and. length > 0 .and. index(value, 'Windows_NT') > 0) then
is_windows = .true.; return
end if

is_windows = .false.
end

!> Version: experimental
!>
!> Whether a file or directory exists at the given path.
Expand Down
15 changes: 15 additions & 0 deletions test/io/test_filesystem.f90
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ subroutine collect_filesystem(testsuite)
type(unittest_type), allocatable, intent(out) :: testsuite(:)

testsuite = [ &
new_unittest("fs_file_is_windows", fs_is_windows), &
new_unittest("fs_file_not_exists", fs_file_not_exists, should_fail=.true.), &
new_unittest("fs_file_exists", fs_file_exists), &
new_unittest("fs_current_dir_exists", fs_current_dir_exists), &
Expand All @@ -30,6 +31,20 @@ subroutine collect_filesystem(testsuite)
]
end

subroutine fs_is_windows(error)
type(error_type), allocatable, intent(out) :: error

character(len=255) :: value
integer :: length, stat

call get_environment_variable('HOMEDRIVE', value, length, stat)
if (is_windows()) then
call check(error, stat == 0 .and. length > 0, "Windows should be detected.")
else
call check(error, stat /= 0 .and. length == 0, "Windows should not be detected.")
end if
end

subroutine fs_file_not_exists(error)
type(error_type), allocatable, intent(out) :: error

Expand Down

0 comments on commit c1830df

Please sign in to comment.