Skip to content

Commit

Permalink
Annotate what we are ending
Browse files Browse the repository at this point in the history
  • Loading branch information
minhqdao committed Oct 8, 2024
1 parent d913f93 commit 9119970
Show file tree
Hide file tree
Showing 2 changed files with 26 additions and 26 deletions.
16 changes: 8 additions & 8 deletions src/stdlib_io_filesystem.F90
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ logical function is_windows()
end if

is_windows = .false.
end
end function

!> Version: experimental
!>
Expand All @@ -43,7 +43,7 @@ character function path_separator()
else
path_separator = '/'
end if
end
end function

!> Version: experimental
!>
Expand All @@ -58,7 +58,7 @@ logical function exists(path)
#if defined(__INTEL_COMPILER)
if (.not. exists) inquire(directory=path, exist=exists)
#endif
end
end function

!> Version: experimental
!>
Expand Down Expand Up @@ -116,7 +116,7 @@ subroutine list_dir(dir, files, iostat, iomsg)
files = [files, string_type(line)]
end do
close(unit, status="delete")
end
end subroutine

!> Version: experimental
!>
Expand All @@ -132,7 +132,7 @@ subroutine mkdir(dir, iostat, iomsg)
else
call run('mkdir -p '//dir, iostat, iomsg)
end if
end
end subroutine

!> Version: experimental
!>
Expand All @@ -146,7 +146,7 @@ subroutine rmdir(dir)
else
call run('rm -rf '//dir)
end if
end
end subroutine

!> Version: experimental
!>
Expand Down Expand Up @@ -177,5 +177,5 @@ subroutine run(command, iostat, iomsg)
end if
if (present(iomsg) .and. trim(adjustl(cmdmsg)) /= '') iomsg = cmdmsg
end if
end
end
end subroutine
end module
36 changes: 18 additions & 18 deletions test/io/test_filesystem.f90
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ subroutine collect_filesystem(testsuite)
new_unittest("fs_rmdir_empty", fs_rmdir_empty), &
new_unittest("fs_rmdir_with_contents", fs_rmdir_with_contents) &
]
end
end subroutine

subroutine fs_is_windows(error)
type(error_type), allocatable, intent(out) :: error
Expand All @@ -46,7 +46,7 @@ subroutine fs_is_windows(error)
else
call check(error, stat /= 0 .and. length == 0, "Windows should not be detected.")
end if
end
end subroutine

subroutine fs_file_not_exists(error)
type(error_type), allocatable, intent(out) :: error
Expand All @@ -55,7 +55,7 @@ subroutine fs_file_not_exists(error)

is_existing = exists("nonexistent")
call check(error, is_existing, "Non-existent file should fail.")
end
end subroutine

subroutine fs_file_exists(error)
type(error_type), allocatable, intent(out) :: error
Expand All @@ -70,7 +70,7 @@ subroutine fs_file_exists(error)
is_existing = exists(filename)
call check(error, is_existing, "An existing file should not fail.")
call delete_file(filename)
end
end subroutine

subroutine fs_current_dir_exists(error)
type(error_type), allocatable, intent(out) :: error
Expand All @@ -79,7 +79,7 @@ subroutine fs_current_dir_exists(error)

is_existing = exists(".")
call check(error, is_existing, "Current directory should not fail.")
end
end subroutine

subroutine fs_path_separator(error)
type(error_type), allocatable, intent(out) :: error
Expand All @@ -94,7 +94,7 @@ subroutine fs_path_separator(error)
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
end subroutine

subroutine fs_run_invalid_command(error)
type(error_type), allocatable, intent(out) :: error
Expand All @@ -103,7 +103,7 @@ subroutine fs_run_invalid_command(error)

call run("invalid_command", iostat=stat)
call check(error, stat, "Running an invalid command should fail.")
end
end subroutine

subroutine fs_run_with_invalid_option(error)
type(error_type), allocatable, intent(out) :: error
Expand All @@ -112,7 +112,7 @@ subroutine fs_run_with_invalid_option(error)

call run("whoami -X", iostat=stat)
call check(error, stat, "Running a valid command with an invalid option should fail.")
end
end subroutine

subroutine fs_run_valid_command(error)
type(error_type), allocatable, intent(out) :: error
Expand All @@ -121,7 +121,7 @@ subroutine fs_run_valid_command(error)

call run("whoami", iostat=stat)
call check(error, stat, "Running a valid command should not fail.")
end
end subroutine

subroutine fs_list_dir_empty(error)
type(error_type), allocatable, intent(out) :: error
Expand All @@ -140,7 +140,7 @@ subroutine fs_list_dir_empty(error)
call check(error, size(files) == 0, "The directory should be empty.")

call rmdir(temp_list_dir)
end
end subroutine

subroutine fs_list_dir_one_file(error)
type(error_type), allocatable, intent(out) :: error
Expand All @@ -167,7 +167,7 @@ subroutine fs_list_dir_one_file(error)
call check(error, char(files(1)) == filename, "The file should be '"//filename//"'.")

call rmdir(temp_list_dir)
end
end subroutine

subroutine fs_list_dir_two_files(error)
type(error_type), allocatable, intent(out) :: error
Expand Down Expand Up @@ -201,7 +201,7 @@ subroutine fs_list_dir_two_files(error)
call check(error, char(files(2)) == filename2, "The file should be '"//filename2//"'.")

call rmdir(temp_list_dir)
end
end subroutine

subroutine fs_list_dir_one_file_one_dir(error)
type(error_type), allocatable, intent(out) :: error
Expand Down Expand Up @@ -239,7 +239,7 @@ subroutine fs_list_dir_one_file_one_dir(error)
call check(error, char(contents(2)) == dir, "The file should be '"//dir//"'.")

call rmdir(temp_list_dir)
end
end subroutine

subroutine fs_rmdir_empty(error)
type(error_type), allocatable, intent(out) :: error
Expand All @@ -252,7 +252,7 @@ subroutine fs_rmdir_empty(error)
call check(error, exists(dir), "Directory should exist.")
call rmdir(dir)
call check(error, .not. exists(dir), "Directory should not exist.")
end
end subroutine

subroutine fs_rmdir_with_contents(error)
type(error_type), allocatable, intent(out) :: error
Expand All @@ -270,7 +270,7 @@ subroutine fs_rmdir_with_contents(error)
end if
call rmdir(dir)
call check(error, .not. exists(dir), "Directory should not exist.")
end
end subroutine

subroutine delete_file(filename)
character(len=*), intent(in) :: filename
Expand All @@ -279,8 +279,8 @@ subroutine delete_file(filename)

open(newunit=io, file=filename)
close(io, status="delete")
end
end
end subroutine
end module

program tester
use, intrinsic :: iso_fortran_env, only : error_unit
Expand All @@ -306,4 +306,4 @@ program tester
write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
error stop
end if
end
end program

0 comments on commit 9119970

Please sign in to comment.