Skip to content

Commit

Permalink
Add path_separator() with tests
Browse files Browse the repository at this point in the history
  • Loading branch information
minhqdao committed Sep 21, 2024
1 parent eeeb634 commit 9da3ea7
Show file tree
Hide file tree
Showing 2 changed files with 32 additions and 2 deletions.
18 changes: 16 additions & 2 deletions src/stdlib_io_filesystem.F90
Original file line number Diff line number Diff line change
Expand Up @@ -6,10 +6,9 @@ module stdlib_io_filesystem
implicit none
private

public :: temp_dir, is_windows, exists, list_dir, mkdir, rmdir, run
public :: temp_dir, is_windows, exists, path_separator, list_dir, mkdir, rmdir, run

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

contains

Expand All @@ -34,6 +33,18 @@ logical function is_windows()
is_windows = .false.
end

!> Version: experimental
!>
!> Separator for paths.
!> [Specification](../page/specs/stdlib_io.html#path_separator)
character function path_separator()
if (is_windows()) then
path_separator = '\'
else
path_separator = '/'
end if
end

!> Version: experimental
!>
!> Whether a file or directory exists at the given path.
Expand Down Expand Up @@ -65,6 +76,7 @@ subroutine list_dir(dir, files, iostat, iomsg)

integer :: unit, stat
character(len=256) :: line
character(:), allocatable :: listed_contents

stat = 0

Expand All @@ -77,6 +89,8 @@ subroutine list_dir(dir, files, iostat, iomsg)
end if
end if

listed_contents = temp_dir//path_separator()//'listed_contents.txt'

if (is_windows()) then
call run('dir /b '//dir//' > '//listed_contents, stat)
else
Expand Down
16 changes: 16 additions & 0 deletions test/io/test_filesystem.f90
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ subroutine collect_filesystem(testsuite)
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), &
new_unittest("fs_path_separator", fs_path_separator), &
new_unittest("fs_run_invalid_command", fs_run_invalid_command, should_fail=.true.), &
new_unittest("fs_run_with_invalid_option", fs_run_with_invalid_option, should_fail=.true.), &
new_unittest("fs_run_valid_command", fs_run_valid_command), &
Expand Down Expand Up @@ -80,6 +81,21 @@ subroutine fs_current_dir_exists(error)
call check(error, is_existing, "Current directory should not fail.")
end

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

character(*), parameter :: outer_dir = "path_separator_outer"
character(*), parameter :: inner_dir = "path_separator_inner"

call rmdir(outer_dir)
call check(error, .not. exists(outer_dir), "Directory should not exist.")
call mkdir(outer_dir)
call check(error, exists(outer_dir), "Outer directory should now exist.")
call mkdir(outer_dir//path_separator()//inner_dir)
call check(error, exists(outer_dir//path_separator()//inner_dir), "Inner directory should now exist.")
call rmdir(outer_dir)
end

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

Expand Down

0 comments on commit 9da3ea7

Please sign in to comment.