@@ -34,17 +34,18 @@ subroutine test_loadtxt_int32(error)
3434 integer (int32), allocatable :: input(:,:), expected(:,:)
3535 real (sp), allocatable :: harvest(:,:)
3636 integer :: n
37-
3837 allocate (harvest(10 ,10 ))
3938 allocate (input(10 ,10 ))
4039 allocate (expected(10 ,10 ))
41-
4240 do n = 1 , 10
4341 call random_number (harvest)
4442 input = int (harvest * 100 )
4543 call savetxt(' test_int32.txt' , input)
4644 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' )
4849 if (allocated (error)) return
4950 end do
5051
@@ -55,17 +56,23 @@ subroutine test_loadtxt_sp(error)
5556 ! > Error handling
5657 type (error_type), allocatable , intent (out ) :: error
5758 real (sp), allocatable :: input(:,:), expected(:,:)
59+ character (len=* ), parameter :: FMT_REAL_SP = ' (es15.8e2)'
5860 integer :: n
5961
6062 allocate (input(10 ,10 ))
6163 allocate (expected(10 ,10 ))
62-
6364 do n = 1 , 10
6465 call random_number (input)
6566 input = input - 0.5
6667 call savetxt(' test_sp.txt' , input)
6768 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' )
6976 if (allocated (error)) return
7077 end do
7178
@@ -77,7 +84,8 @@ subroutine test_loadtxt_sp_huge(error)
7784 type (error_type), allocatable , intent (out ) :: error
7885 real (sp), allocatable :: input(:,:), expected(:,:)
7986 integer :: n
80-
87+ character (len=* ), parameter :: FMT_REAL_SP = ' (es15.8e2)'
88+
8189 allocate (input(10 ,10 ))
8290 allocate (expected(10 ,10 ))
8391
@@ -86,7 +94,13 @@ subroutine test_loadtxt_sp_huge(error)
8694 input = (input - 0.5 ) * huge (input)
8795 call savetxt(' test_sp_huge.txt' , input)
8896 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' )
90104 if (allocated (error)) return
91105 end do
92106
@@ -98,6 +112,7 @@ subroutine test_loadtxt_sp_tiny(error)
98112 type (error_type), allocatable , intent (out ) :: error
99113 real (sp), allocatable :: input(:,:), expected(:,:)
100114 integer :: n
115+ character (len=* ), parameter :: FMT_REAL_SP = ' (es15.8e2)'
101116
102117 allocate (input(10 ,10 ))
103118 allocate (expected(10 ,10 ))
@@ -107,7 +122,13 @@ subroutine test_loadtxt_sp_tiny(error)
107122 input = (input - 0.5 ) * tiny (input)
108123 call savetxt(' test_sp_tiny.txt' , input)
109124 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' )
111132 if (allocated (error)) return
112133 end do
113134
@@ -119,6 +140,7 @@ subroutine test_loadtxt_dp(error)
119140 type (error_type), allocatable , intent (out ) :: error
120141 real (dp), allocatable :: input(:,:), expected(:,:)
121142 integer :: n
143+ character (len=* ), parameter :: FMT_REAL_DP = ' (es24.16e3)'
122144
123145 allocate (input(10 ,10 ))
124146 allocate (expected(10 ,10 ))
@@ -128,7 +150,13 @@ subroutine test_loadtxt_dp(error)
128150 input = input - 0.5
129151 call savetxt(' test_dp.txt' , input)
130152 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' )
132160 if (allocated (error)) return
133161 end do
134162
@@ -140,6 +168,7 @@ subroutine test_loadtxt_dp_max_skip(error)
140168 type (error_type), allocatable , intent (out ) :: error
141169 real (dp), allocatable :: input(:,:), expected(:,:)
142170 integer :: n, m
171+ character (len=* ), parameter :: FMT_REAL_DP = ' (es24.16e3)'
143172
144173 allocate (input(10 ,10 ))
145174
@@ -149,7 +178,13 @@ subroutine test_loadtxt_dp_max_skip(error)
149178 input = input - 0.5
150179 call savetxt(' test_dp_max_skip.txt' , input)
151180 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' )
153188 deallocate (expected)
154189 if (allocated (error)) return
155190 end do
@@ -163,6 +198,7 @@ subroutine test_loadtxt_dp_huge(error)
163198 type (error_type), allocatable , intent (out ) :: error
164199 real (dp), allocatable :: input(:,:), expected(:,:)
165200 integer :: n
201+ character (len=* ), parameter :: FMT_REAL_DP = ' (es24.16e3)'
166202
167203 allocate (input(10 ,10 ))
168204 allocate (expected(10 ,10 ))
@@ -172,7 +208,13 @@ subroutine test_loadtxt_dp_huge(error)
172208 input = (input - 0.5 ) * huge (input)
173209 call savetxt(' test_dp_huge.txt' , input)
174210 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' )
176218 if (allocated (error)) return
177219 end do
178220
@@ -184,7 +226,8 @@ subroutine test_loadtxt_dp_tiny(error)
184226 type (error_type), allocatable , intent (out ) :: error
185227 real (dp), allocatable :: input(:,:), expected(:,:)
186228 integer :: n
187-
229+ character (len=* ), parameter :: FMT_REAL_DP = ' (es24.16e3)'
230+
188231 allocate (input(10 ,10 ))
189232 allocate (expected(10 ,10 ))
190233
@@ -193,7 +236,13 @@ subroutine test_loadtxt_dp_tiny(error)
193236 input = (input - 0.5 ) * tiny (input)
194237 call savetxt(' test_dp_tiny.txt' , input)
195238 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' )
197246 if (allocated (error)) return
198247 end do
199248
@@ -206,6 +255,7 @@ subroutine test_loadtxt_complex(error)
206255 complex (dp), allocatable :: input(:,:), expected(:,:)
207256 real (dp), allocatable :: re(:,:), im(:,:)
208257 integer :: n
258+ character (len=* ), parameter :: FMT_COMPLEX_DP = ' (es24.16e3,1x,es24.16e3)'
209259
210260 allocate (re(10 ,10 ))
211261 allocate (im(10 ,10 ))
@@ -219,6 +269,8 @@ subroutine test_loadtxt_complex(error)
219269 call savetxt(' test_complex.txt' , input)
220270 call loadtxt(' test_complex.txt' , expected)
221271 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))
222274 if (allocated (error)) return
223275 end do
224276
@@ -237,7 +289,6 @@ program tester
237289 character (len=* ), parameter :: fmt = ' ("#", *(1x, a))'
238290
239291 stat = 0
240-
241292 testsuites = [ &
242293 new_testsuite(" loadtxt" , collect_loadtxt) &
243294 ]
0 commit comments