11! SPDX-Identifier: MIT
22
3- ! > Interaction with the filesystem.
3+ !> Interaction with the filesystem.
44module stdlib_io_filesystem
55 use stdlib_string_type, only: string_type
66 implicit none
77 private
88
99 public :: temp_dir, is_windows, exists, path_separator, list_dir, mkdir, rmdir, run
1010
11+ #: if OS == 'Windows'
12+ logical, parameter :: is_windows = .true.
13+ character, parameter :: path_separator = '\'
14+ #: else
15+ logical, parameter :: is_windows = .false.
16+ character, parameter :: path_separator = '/'
17+ #: endif
18+
1119 character(*), parameter :: temp_dir = 'temp'
1220
1321contains
14-
15- ! > Version: experimental
16- ! >
17- ! > Whether the operating system is Windows.
18- ! > [Specification](../page/specs/stdlib_io.html#is_windows)
19- logical function is_windows ()
20- character (len= 255 ) :: value
21- integer :: length, stat
22-
23- call get_environment_variable(' OSTYPE' , value, length, stat)
24- if (stat == 0 .and. length > 0 .and. (index (value, ' win' ) > 0 .or. index (value, ' msys' ) > 0 )) then
25- is_windows = .true. ; return
26- end if
27-
28- call get_environment_variable(' OS' , value, length, stat)
29- if (stat == 0 .and. length > 0 .and. index (value, ' Windows_NT' ) > 0 ) then
30- is_windows = .true. ; return
31- end if
32-
33- is_windows = .false.
34- end function
35-
36- ! > Version: experimental
37- ! >
38- ! > Returns the path separator for the current operating system.
39- ! > [Specification](../page/specs/stdlib_io.html#path_separator)
40- character function path_separator ()
41- if (is_windows()) then
42- path_separator = ' \'
43- else
44- path_separator = ' /'
45- end if
46- end function
47-
4822 !> Version: experimental
4923 !>
5024 !> Whether a file or directory exists at the given path.
@@ -89,9 +63,9 @@ subroutine list_dir(dir, files, iostat, iomsg)
8963 end if
9064 end if
9165
92- listed_contents = temp_dir// path_separator() // ' listed_contents.txt'
66+ listed_contents = temp_dir//path_separator//'listed_contents.txt'
9367
94- if (is_windows() ) then
68+ if (is_windows) then
9569 call run('dir /b '//dir//' > '//listed_contents, stat)
9670 else
9771 call run('ls '//dir//' > '//listed_contents, stat)
@@ -127,7 +101,7 @@ subroutine mkdir(dir, iostat, iomsg)
127101 integer, optional, intent(out) :: iostat
128102 character(len=:), allocatable, optional, intent(out) :: iomsg
129103
130- if (is_windows() ) then
104+ if (is_windows) then
131105 call run('mkdir '//dir, iostat, iomsg)
132106 else
133107 call run('mkdir -p '//dir, iostat, iomsg)
@@ -141,7 +115,7 @@ subroutine mkdir(dir, iostat, iomsg)
141115 subroutine rmdir(dir)
142116 character(len=*), intent(in) :: dir
143117
144- if (is_windows() ) then
118+ if (is_windows) then
145119 call run('rmdir /s/q '//dir)
146120 else
147121 call run('rm -rf '//dir)
0 commit comments