1
1
module test_getline
2
- use stdlib_io, only : getline
3
- use stdlib_string_type, only : string_type, len
2
+ use stdlib_io, only : getline, getfile
3
+ use stdlib_error, only: state_type
4
+ use stdlib_string_type, only : string_type, len, len_trim
4
5
use testdrive, only : new_unittest, unittest_type, error_type, check
5
6
implicit none
6
7
private
@@ -20,7 +21,10 @@ subroutine collect_getline(testsuite)
20
21
new_unittest(" pad-no" , test_pad_no), &
21
22
new_unittest(" iostat-end" , test_iostat_end), &
22
23
new_unittest(" closed-unit" , test_closed_unit, should_fail= .true. ), &
23
- new_unittest(" no-unit" , test_no_unit, should_fail= .true. ) &
24
+ new_unittest(" no-unit" , test_no_unit, should_fail= .true. ), &
25
+ new_unittest(" getfile-no" , test_getfile_missing), &
26
+ new_unittest(" getfile-empty" , test_getfile_empty), &
27
+ new_unittest(" getfile-non-empty" , test_getfile_non_empty) &
24
28
]
25
29
end subroutine collect_getline
26
30
@@ -139,6 +143,77 @@ subroutine test_no_unit(error)
139
143
call check(error, stat, msg)
140
144
end subroutine test_no_unit
141
145
146
+ subroutine test_getfile_missing (error )
147
+ ! > Test for a missing file.
148
+ type (error_type), allocatable , intent (out ) :: error
149
+
150
+ type (string_type) :: fileContents
151
+ type (state_type) :: err
152
+
153
+ fileContents = getfile(" nonexistent_file.txt" , err)
154
+
155
+ ! Check that an error was returned
156
+ call check(error, err% error(), " Error not returned on a missing file" )
157
+ if (allocated (error)) return
158
+
159
+ end subroutine test_getfile_missing
160
+
161
+ subroutine test_getfile_empty (error )
162
+ ! > Test for an empty file.
163
+ type (error_type), allocatable , intent (out ) :: error
164
+
165
+ integer :: ios
166
+ character (len= :), allocatable :: filename
167
+ type (string_type) :: fileContents
168
+ type (state_type) :: err
169
+
170
+ ! Get a temporary file name
171
+ filename = " test_getfile_empty.txt"
172
+
173
+ ! Create an empty file
174
+ open (newunit= ios, file= filename, action= " write" , form= " formatted" , access= " sequential" )
175
+ close (ios)
176
+
177
+ ! Read and delete it
178
+ fileContents = getfile(filename, err, delete= .true. )
179
+
180
+ call check(error, err% ok(), " Should not return error reading an empty file" )
181
+ if (allocated (error)) return
182
+
183
+ call check(error, len_trim (fileContents) == 0 , " String from empty file should be empty" )
184
+ if (allocated (error)) return
185
+
186
+ end subroutine test_getfile_empty
187
+
188
+ subroutine test_getfile_non_empty (error )
189
+ ! > Test for a non-empty file.
190
+ type (error_type), allocatable , intent (out ) :: error
191
+
192
+ integer :: ios
193
+ character (len= :), allocatable :: filename
194
+ type (string_type) :: fileContents
195
+ type (state_type) :: err
196
+
197
+ ! Get a temporary file name
198
+ filename = " test_getfile_size5.txt"
199
+
200
+ ! Create a fixed-size file
201
+ open (newunit= ios, file= filename, action= " write" , form= " unformatted" , access= " stream" )
202
+ write (ios) " 12345"
203
+ close (ios)
204
+
205
+ ! Read and delete it
206
+ fileContents = getfile(filename, err, delete= .true. )
207
+
208
+ call check(error, err% ok(), " Should not return error reading a non-empty file" )
209
+ if (allocated (error)) return
210
+
211
+ call check(error, len_trim (fileContents) == 5 , " Wrong string size returned" )
212
+ if (allocated (error)) return
213
+
214
+ end subroutine test_getfile_non_empty
215
+
216
+
142
217
end module test_getline
143
218
144
219
0 commit comments