@@ -32,7 +32,7 @@ subroutine collect_filesystem(testsuite)
32
32
new_unittest(" fs_rmdir_empty" , fs_rmdir_empty), &
33
33
new_unittest(" fs_rmdir_with_contents" , fs_rmdir_with_contents) &
34
34
]
35
- end
35
+ end subroutine
36
36
37
37
subroutine fs_is_windows (error )
38
38
type (error_type), allocatable , intent (out ) :: error
@@ -46,7 +46,7 @@ subroutine fs_is_windows(error)
46
46
else
47
47
call check(error, stat /= 0 .and. length == 0 , " Windows should not be detected." )
48
48
end if
49
- end
49
+ end subroutine
50
50
51
51
subroutine fs_file_not_exists (error )
52
52
type (error_type), allocatable , intent (out ) :: error
@@ -55,7 +55,7 @@ subroutine fs_file_not_exists(error)
55
55
56
56
is_existing = exists(" nonexistent" )
57
57
call check(error, is_existing, " Non-existent file should fail." )
58
- end
58
+ end subroutine
59
59
60
60
subroutine fs_file_exists (error )
61
61
type (error_type), allocatable , intent (out ) :: error
@@ -70,7 +70,7 @@ subroutine fs_file_exists(error)
70
70
is_existing = exists(filename)
71
71
call check(error, is_existing, " An existing file should not fail." )
72
72
call delete_file(filename)
73
- end
73
+ end subroutine
74
74
75
75
subroutine fs_current_dir_exists (error )
76
76
type (error_type), allocatable , intent (out ) :: error
@@ -79,7 +79,7 @@ subroutine fs_current_dir_exists(error)
79
79
80
80
is_existing = exists(" ." )
81
81
call check(error, is_existing, " Current directory should not fail." )
82
- end
82
+ end subroutine
83
83
84
84
subroutine fs_path_separator (error )
85
85
type (error_type), allocatable , intent (out ) :: error
@@ -94,7 +94,7 @@ subroutine fs_path_separator(error)
94
94
call mkdir(outer_dir// path_separator()// inner_dir)
95
95
call check(error, exists(outer_dir// path_separator()// inner_dir), " Inner directory should now exist." )
96
96
call rmdir(outer_dir)
97
- end
97
+ end subroutine
98
98
99
99
subroutine fs_run_invalid_command (error )
100
100
type (error_type), allocatable , intent (out ) :: error
@@ -103,7 +103,7 @@ subroutine fs_run_invalid_command(error)
103
103
104
104
call run(" invalid_command" , iostat= stat)
105
105
call check(error, stat, " Running an invalid command should fail." )
106
- end
106
+ end subroutine
107
107
108
108
subroutine fs_run_with_invalid_option (error )
109
109
type (error_type), allocatable , intent (out ) :: error
@@ -112,7 +112,7 @@ subroutine fs_run_with_invalid_option(error)
112
112
113
113
call run(" whoami -X" , iostat= stat)
114
114
call check(error, stat, " Running a valid command with an invalid option should fail." )
115
- end
115
+ end subroutine
116
116
117
117
subroutine fs_run_valid_command (error )
118
118
type (error_type), allocatable , intent (out ) :: error
@@ -121,7 +121,7 @@ subroutine fs_run_valid_command(error)
121
121
122
122
call run(" whoami" , iostat= stat)
123
123
call check(error, stat, " Running a valid command should not fail." )
124
- end
124
+ end subroutine
125
125
126
126
subroutine fs_list_dir_empty (error )
127
127
type (error_type), allocatable , intent (out ) :: error
@@ -140,7 +140,7 @@ subroutine fs_list_dir_empty(error)
140
140
call check(error, size (files) == 0 , " The directory should be empty." )
141
141
142
142
call rmdir(temp_list_dir)
143
- end
143
+ end subroutine
144
144
145
145
subroutine fs_list_dir_one_file (error )
146
146
type (error_type), allocatable , intent (out ) :: error
@@ -167,7 +167,7 @@ subroutine fs_list_dir_one_file(error)
167
167
call check(error, char (files(1 )) == filename, " The file should be '" // filename// " '." )
168
168
169
169
call rmdir(temp_list_dir)
170
- end
170
+ end subroutine
171
171
172
172
subroutine fs_list_dir_two_files (error )
173
173
type (error_type), allocatable , intent (out ) :: error
@@ -201,7 +201,7 @@ subroutine fs_list_dir_two_files(error)
201
201
call check(error, char (files(2 )) == filename2, " The file should be '" // filename2// " '." )
202
202
203
203
call rmdir(temp_list_dir)
204
- end
204
+ end subroutine
205
205
206
206
subroutine fs_list_dir_one_file_one_dir (error )
207
207
type (error_type), allocatable , intent (out ) :: error
@@ -239,7 +239,7 @@ subroutine fs_list_dir_one_file_one_dir(error)
239
239
call check(error, char (contents(2 )) == dir, " The file should be '" // dir// " '." )
240
240
241
241
call rmdir(temp_list_dir)
242
- end
242
+ end subroutine
243
243
244
244
subroutine fs_rmdir_empty (error )
245
245
type (error_type), allocatable , intent (out ) :: error
@@ -252,7 +252,7 @@ subroutine fs_rmdir_empty(error)
252
252
call check(error, exists(dir), " Directory should exist." )
253
253
call rmdir(dir)
254
254
call check(error, .not. exists(dir), " Directory should not exist." )
255
- end
255
+ end subroutine
256
256
257
257
subroutine fs_rmdir_with_contents (error )
258
258
type (error_type), allocatable , intent (out ) :: error
@@ -270,7 +270,7 @@ subroutine fs_rmdir_with_contents(error)
270
270
end if
271
271
call rmdir(dir)
272
272
call check(error, .not. exists(dir), " Directory should not exist." )
273
- end
273
+ end subroutine
274
274
275
275
subroutine delete_file (filename )
276
276
character (len=* ), intent (in ) :: filename
@@ -279,8 +279,8 @@ subroutine delete_file(filename)
279
279
280
280
open (newunit= io, file= filename)
281
281
close (io, status= " delete" )
282
- end
283
- end
282
+ end subroutine
283
+ end module
284
284
285
285
program tester
286
286
use , intrinsic :: iso_fortran_env, only : error_unit
@@ -306,4 +306,4 @@ program tester
306
306
write (error_unit, ' (i0, 1x, a)' ) stat, " test(s) failed!"
307
307
error stop
308
308
end if
309
- end
309
+ end program
0 commit comments