Skip to content

Commit 9119970

Browse files
committed
Annotate what we are ending
1 parent d913f93 commit 9119970

File tree

2 files changed

+26
-26
lines changed

2 files changed

+26
-26
lines changed

src/stdlib_io_filesystem.F90

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ logical function is_windows()
3131
end if
3232

3333
is_windows = .false.
34-
end
34+
end function
3535

3636
!> Version: experimental
3737
!>
@@ -43,7 +43,7 @@ character function path_separator()
4343
else
4444
path_separator = '/'
4545
end if
46-
end
46+
end function
4747

4848
!> Version: experimental
4949
!>
@@ -58,7 +58,7 @@ logical function exists(path)
5858
#if defined(__INTEL_COMPILER)
5959
if (.not. exists) inquire(directory=path, exist=exists)
6060
#endif
61-
end
61+
end function
6262

6363
!> Version: experimental
6464
!>
@@ -116,7 +116,7 @@ subroutine list_dir(dir, files, iostat, iomsg)
116116
files = [files, string_type(line)]
117117
end do
118118
close(unit, status="delete")
119-
end
119+
end subroutine
120120

121121
!> Version: experimental
122122
!>
@@ -132,7 +132,7 @@ subroutine mkdir(dir, iostat, iomsg)
132132
else
133133
call run('mkdir -p '//dir, iostat, iomsg)
134134
end if
135-
end
135+
end subroutine
136136

137137
!> Version: experimental
138138
!>
@@ -146,7 +146,7 @@ subroutine rmdir(dir)
146146
else
147147
call run('rm -rf '//dir)
148148
end if
149-
end
149+
end subroutine
150150

151151
!> Version: experimental
152152
!>
@@ -177,5 +177,5 @@ subroutine run(command, iostat, iomsg)
177177
end if
178178
if (present(iomsg) .and. trim(adjustl(cmdmsg)) /= '') iomsg = cmdmsg
179179
end if
180-
end
181-
end
180+
end subroutine
181+
end module

test/io/test_filesystem.f90

Lines changed: 18 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ subroutine collect_filesystem(testsuite)
3232
new_unittest("fs_rmdir_empty", fs_rmdir_empty), &
3333
new_unittest("fs_rmdir_with_contents", fs_rmdir_with_contents) &
3434
]
35-
end
35+
end subroutine
3636

3737
subroutine fs_is_windows(error)
3838
type(error_type), allocatable, intent(out) :: error
@@ -46,7 +46,7 @@ subroutine fs_is_windows(error)
4646
else
4747
call check(error, stat /= 0 .and. length == 0, "Windows should not be detected.")
4848
end if
49-
end
49+
end subroutine
5050

5151
subroutine fs_file_not_exists(error)
5252
type(error_type), allocatable, intent(out) :: error
@@ -55,7 +55,7 @@ subroutine fs_file_not_exists(error)
5555

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

6060
subroutine fs_file_exists(error)
6161
type(error_type), allocatable, intent(out) :: error
@@ -70,7 +70,7 @@ subroutine fs_file_exists(error)
7070
is_existing = exists(filename)
7171
call check(error, is_existing, "An existing file should not fail.")
7272
call delete_file(filename)
73-
end
73+
end subroutine
7474

7575
subroutine fs_current_dir_exists(error)
7676
type(error_type), allocatable, intent(out) :: error
@@ -79,7 +79,7 @@ subroutine fs_current_dir_exists(error)
7979

8080
is_existing = exists(".")
8181
call check(error, is_existing, "Current directory should not fail.")
82-
end
82+
end subroutine
8383

8484
subroutine fs_path_separator(error)
8585
type(error_type), allocatable, intent(out) :: error
@@ -94,7 +94,7 @@ subroutine fs_path_separator(error)
9494
call mkdir(outer_dir//path_separator()//inner_dir)
9595
call check(error, exists(outer_dir//path_separator()//inner_dir), "Inner directory should now exist.")
9696
call rmdir(outer_dir)
97-
end
97+
end subroutine
9898

9999
subroutine fs_run_invalid_command(error)
100100
type(error_type), allocatable, intent(out) :: error
@@ -103,7 +103,7 @@ subroutine fs_run_invalid_command(error)
103103

104104
call run("invalid_command", iostat=stat)
105105
call check(error, stat, "Running an invalid command should fail.")
106-
end
106+
end subroutine
107107

108108
subroutine fs_run_with_invalid_option(error)
109109
type(error_type), allocatable, intent(out) :: error
@@ -112,7 +112,7 @@ subroutine fs_run_with_invalid_option(error)
112112

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

117117
subroutine fs_run_valid_command(error)
118118
type(error_type), allocatable, intent(out) :: error
@@ -121,7 +121,7 @@ subroutine fs_run_valid_command(error)
121121

122122
call run("whoami", iostat=stat)
123123
call check(error, stat, "Running a valid command should not fail.")
124-
end
124+
end subroutine
125125

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

142142
call rmdir(temp_list_dir)
143-
end
143+
end subroutine
144144

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

169169
call rmdir(temp_list_dir)
170-
end
170+
end subroutine
171171

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

203203
call rmdir(temp_list_dir)
204-
end
204+
end subroutine
205205

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

241241
call rmdir(temp_list_dir)
242-
end
242+
end subroutine
243243

244244
subroutine fs_rmdir_empty(error)
245245
type(error_type), allocatable, intent(out) :: error
@@ -252,7 +252,7 @@ subroutine fs_rmdir_empty(error)
252252
call check(error, exists(dir), "Directory should exist.")
253253
call rmdir(dir)
254254
call check(error, .not. exists(dir), "Directory should not exist.")
255-
end
255+
end subroutine
256256

257257
subroutine fs_rmdir_with_contents(error)
258258
type(error_type), allocatable, intent(out) :: error
@@ -270,7 +270,7 @@ subroutine fs_rmdir_with_contents(error)
270270
end if
271271
call rmdir(dir)
272272
call check(error, .not. exists(dir), "Directory should not exist.")
273-
end
273+
end subroutine
274274

275275
subroutine delete_file(filename)
276276
character(len=*), intent(in) :: filename
@@ -279,8 +279,8 @@ subroutine delete_file(filename)
279279

280280
open(newunit=io, file=filename)
281281
close(io, status="delete")
282-
end
283-
end
282+
end subroutine
283+
end module
284284

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

0 commit comments

Comments
 (0)