@@ -34,17 +34,18 @@ subroutine test_loadtxt_int32(error)
34
34
integer (int32), allocatable :: input(:,:), expected(:,:)
35
35
real (sp), allocatable :: harvest(:,:)
36
36
integer :: n
37
-
38
37
allocate (harvest(10 ,10 ))
39
38
allocate (input(10 ,10 ))
40
39
allocate (expected(10 ,10 ))
41
-
42
40
do n = 1 , 10
43
41
call random_number (harvest)
44
42
input = int (harvest * 100 )
45
43
call savetxt(' test_int32.txt' , input)
46
44
call loadtxt(' test_int32.txt' , expected)
47
- call check(error, all (input == expected))
45
+ call check(error, all (input == expected),' Default list directed read failed' )
46
+ if (allocated (error)) return
47
+ call loadtxt(' test_int32.txt' , expected, fmt= ' *' )
48
+ call check(error, all (input == expected),' User specified list directed read faile' )
48
49
if (allocated (error)) return
49
50
end do
50
51
@@ -55,17 +56,23 @@ subroutine test_loadtxt_sp(error)
55
56
! > Error handling
56
57
type (error_type), allocatable , intent (out ) :: error
57
58
real (sp), allocatable :: input(:,:), expected(:,:)
59
+ character (len=* ), parameter :: FMT_REAL_SP = ' (es15.8e2)'
58
60
integer :: n
59
61
60
62
allocate (input(10 ,10 ))
61
63
allocate (expected(10 ,10 ))
62
-
63
64
do n = 1 , 10
64
65
call random_number (input)
65
66
input = input - 0.5
66
67
call savetxt(' test_sp.txt' , input)
67
68
call loadtxt(' test_sp.txt' , expected)
68
- call check(error, all (input == expected))
69
+ call check(error, all (input == expected),' Default format read failed' )
70
+ if (allocated (error)) return
71
+ call loadtxt(' test_sp.txt' , expected, fmt= ' *' )
72
+ call check(error, all (input == expected),' List directed read failed' )
73
+ if (allocated (error)) return
74
+ call loadtxt(' test_sp.txt' , expected, fmt= " (*" // FMT_REAL_sp(1 :len (FMT_REAL_sp)- 1 )// " ,1x))" )
75
+ call check(error, all (input == expected),' User specified format failed' )
69
76
if (allocated (error)) return
70
77
end do
71
78
@@ -77,7 +84,8 @@ subroutine test_loadtxt_sp_huge(error)
77
84
type (error_type), allocatable , intent (out ) :: error
78
85
real (sp), allocatable :: input(:,:), expected(:,:)
79
86
integer :: n
80
-
87
+ character (len=* ), parameter :: FMT_REAL_SP = ' (es15.8e2)'
88
+
81
89
allocate (input(10 ,10 ))
82
90
allocate (expected(10 ,10 ))
83
91
@@ -86,7 +94,13 @@ subroutine test_loadtxt_sp_huge(error)
86
94
input = (input - 0.5 ) * huge (input)
87
95
call savetxt(' test_sp_huge.txt' , input)
88
96
call loadtxt(' test_sp_huge.txt' , expected)
89
- call check(error, all (input == expected))
97
+ call check(error, all (input == expected),' Default format read failed' )
98
+ if (allocated (error)) return
99
+ call loadtxt(' test_sp_huge.txt' , expected, fmt= ' *' )
100
+ call check(error, all (input == expected),' List directed read failed' )
101
+ if (allocated (error)) return
102
+ call loadtxt(' test_sp_huge.txt' , expected, fmt= " (*" // FMT_REAL_sp(1 :len (FMT_REAL_sp)- 1 )// " ,1x))" )
103
+ call check(error, all (input == expected),' User specified format failed' )
90
104
if (allocated (error)) return
91
105
end do
92
106
@@ -98,6 +112,7 @@ subroutine test_loadtxt_sp_tiny(error)
98
112
type (error_type), allocatable , intent (out ) :: error
99
113
real (sp), allocatable :: input(:,:), expected(:,:)
100
114
integer :: n
115
+ character (len=* ), parameter :: FMT_REAL_SP = ' (es15.8e2)'
101
116
102
117
allocate (input(10 ,10 ))
103
118
allocate (expected(10 ,10 ))
@@ -107,7 +122,13 @@ subroutine test_loadtxt_sp_tiny(error)
107
122
input = (input - 0.5 ) * tiny (input)
108
123
call savetxt(' test_sp_tiny.txt' , input)
109
124
call loadtxt(' test_sp_tiny.txt' , expected)
110
- call check(error, all (input == expected))
125
+ call check(error, all (input == expected),' Default format read failed' )
126
+ if (allocated (error)) return
127
+ call loadtxt(' test_sp_tiny.txt' , expected, fmt= ' *' )
128
+ call check(error, all (input == expected),' List directed read failed' )
129
+ if (allocated (error)) return
130
+ call loadtxt(' test_sp_tiny.txt' , expected, fmt= " (*" // FMT_REAL_sp(1 :len (FMT_REAL_sp)- 1 )// " ,1x))" )
131
+ call check(error, all (input == expected),' User specified format failed' )
111
132
if (allocated (error)) return
112
133
end do
113
134
@@ -119,6 +140,7 @@ subroutine test_loadtxt_dp(error)
119
140
type (error_type), allocatable , intent (out ) :: error
120
141
real (dp), allocatable :: input(:,:), expected(:,:)
121
142
integer :: n
143
+ character (len=* ), parameter :: FMT_REAL_DP = ' (es24.16e3)'
122
144
123
145
allocate (input(10 ,10 ))
124
146
allocate (expected(10 ,10 ))
@@ -128,7 +150,13 @@ subroutine test_loadtxt_dp(error)
128
150
input = input - 0.5
129
151
call savetxt(' test_dp.txt' , input)
130
152
call loadtxt(' test_dp.txt' , expected)
131
- call check(error, all (input == expected))
153
+ call check(error, all (input == expected),' Default format read failed' )
154
+ if (allocated (error)) return
155
+ call loadtxt(' test_dp.txt' , expected, fmt= ' *' )
156
+ call check(error, all (input == expected),' List directed read failed' )
157
+ if (allocated (error)) return
158
+ call loadtxt(' test_dp.txt' , expected, fmt= " (*" // FMT_REAL_dp(1 :len (FMT_REAL_dp)- 1 )// " ,1x))" )
159
+ call check(error, all (input == expected),' User specified format failed' )
132
160
if (allocated (error)) return
133
161
end do
134
162
@@ -140,6 +168,7 @@ subroutine test_loadtxt_dp_max_skip(error)
140
168
type (error_type), allocatable , intent (out ) :: error
141
169
real (dp), allocatable :: input(:,:), expected(:,:)
142
170
integer :: n, m
171
+ character (len=* ), parameter :: FMT_REAL_DP = ' (es24.16e3)'
143
172
144
173
allocate (input(10 ,10 ))
145
174
@@ -149,7 +178,13 @@ subroutine test_loadtxt_dp_max_skip(error)
149
178
input = input - 0.5
150
179
call savetxt(' test_dp_max_skip.txt' , input)
151
180
call loadtxt(' test_dp_max_skip.txt' , expected, skiprows= m, max_rows= n)
152
- call check(error, all (input(m+1 :min (n+ m,10 ),:) == expected))
181
+ call check(error, all (input(m+1 :min (n+ m,10 ),:) == expected),' Default format read failed' )
182
+ if (allocated (error)) return
183
+ call loadtxt(' test_dp_max_skip.txt' , expected, skiprows= m, max_rows= n, fmt= ' *' )
184
+ call check(error, all (input(m+1 :min (n+ m,10 ),:) == expected),' List directed read failed' )
185
+ if (allocated (error)) return
186
+ call loadtxt(' test_dp_max_skip.txt' , expected, fmt= " (*" // FMT_REAL_dp(1 :len (FMT_REAL_dp)- 1 )// " ,1x))" )
187
+ call check(error, all (input == expected),' User specified format failed' )
153
188
deallocate (expected)
154
189
if (allocated (error)) return
155
190
end do
@@ -163,6 +198,7 @@ subroutine test_loadtxt_dp_huge(error)
163
198
type (error_type), allocatable , intent (out ) :: error
164
199
real (dp), allocatable :: input(:,:), expected(:,:)
165
200
integer :: n
201
+ character (len=* ), parameter :: FMT_REAL_DP = ' (es24.16e3)'
166
202
167
203
allocate (input(10 ,10 ))
168
204
allocate (expected(10 ,10 ))
@@ -172,7 +208,13 @@ subroutine test_loadtxt_dp_huge(error)
172
208
input = (input - 0.5 ) * huge (input)
173
209
call savetxt(' test_dp_huge.txt' , input)
174
210
call loadtxt(' test_dp_huge.txt' , expected)
175
- call check(error, all (input == expected))
211
+ call check(error, all (input == expected),' Default format read failed' )
212
+ if (allocated (error)) return
213
+ call loadtxt(' test_dp_huge.txt' , expected, fmt= ' *' )
214
+ call check(error, all (input == expected),' List directed read failed' )
215
+ if (allocated (error)) return
216
+ call loadtxt(' test_dp_huge.txt' , expected, fmt= " (*" // FMT_REAL_dp(1 :len (FMT_REAL_dp)- 1 )// " ,1x))" )
217
+ call check(error, all (input == expected),' User specified format failed' )
176
218
if (allocated (error)) return
177
219
end do
178
220
@@ -184,7 +226,8 @@ subroutine test_loadtxt_dp_tiny(error)
184
226
type (error_type), allocatable , intent (out ) :: error
185
227
real (dp), allocatable :: input(:,:), expected(:,:)
186
228
integer :: n
187
-
229
+ character (len=* ), parameter :: FMT_REAL_DP = ' (es24.16e3)'
230
+
188
231
allocate (input(10 ,10 ))
189
232
allocate (expected(10 ,10 ))
190
233
@@ -193,7 +236,13 @@ subroutine test_loadtxt_dp_tiny(error)
193
236
input = (input - 0.5 ) * tiny (input)
194
237
call savetxt(' test_dp_tiny.txt' , input)
195
238
call loadtxt(' test_dp_tiny.txt' , expected)
196
- call check(error, all (input == expected))
239
+ call check(error, all (input == expected),' Default format read failed' )
240
+ if (allocated (error)) return
241
+ call loadtxt(' test_dp_tiny.txt' , expected, fmt= ' *' )
242
+ call check(error, all (input == expected),' List directed read failed' )
243
+ if (allocated (error)) return
244
+ call loadtxt(' test_dp_tiny.txt' , expected, fmt= " (*" // FMT_REAL_dp(1 :len (FMT_REAL_dp)- 1 )// " ,1x))" )
245
+ call check(error, all (input == expected),' User specified format failed' )
197
246
if (allocated (error)) return
198
247
end do
199
248
@@ -206,6 +255,7 @@ subroutine test_loadtxt_complex(error)
206
255
complex (dp), allocatable :: input(:,:), expected(:,:)
207
256
real (dp), allocatable :: re(:,:), im(:,:)
208
257
integer :: n
258
+ character (len=* ), parameter :: FMT_COMPLEX_DP = ' (es24.16e3,1x,es24.16e3)'
209
259
210
260
allocate (re(10 ,10 ))
211
261
allocate (im(10 ,10 ))
@@ -219,6 +269,8 @@ subroutine test_loadtxt_complex(error)
219
269
call savetxt(' test_complex.txt' , input)
220
270
call loadtxt(' test_complex.txt' , expected)
221
271
call check(error, all (input == expected))
272
+ call loadtxt(' test_complex.txt' , expected, fmt= " (*" // FMT_COMPLEX_dp(1 :len (FMT_COMPLEX_dp)- 1 )// " ,1x))" )
273
+ call check(error, all (input == expected))
222
274
if (allocated (error)) return
223
275
end do
224
276
@@ -237,7 +289,6 @@ program tester
237
289
character (len=* ), parameter :: fmt = ' ("#", *(1x, a))'
238
290
239
291
stat = 0
240
-
241
292
testsuites = [ &
242
293
new_testsuite(" loadtxt" , collect_loadtxt) &
243
294
]
0 commit comments