Skip to content

Commit 206f84a

Browse files
authored
Merge pull request #805 from chuckyvt/loadtxt-real-format-update
Loadtxt real format update to list directed
2 parents d44d625 + 285cbae commit 206f84a

File tree

4 files changed

+122
-25
lines changed

4 files changed

+122
-25
lines changed

doc/specs/stdlib_io.md

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ Loads a rank-2 `array` from a text file.
1717

1818
### Syntax
1919

20-
`call ` [[stdlib_io(module):loadtxt(interface)]] `(filename, array [, skiprows] [, max_rows])`
20+
`call ` [[stdlib_io(module):loadtxt(interface)]] `(filename, array [, skiprows] [, max_rows] [, fmt])`
2121

2222
### Arguments
2323

@@ -29,6 +29,10 @@ Loads a rank-2 `array` from a text file.
2929

3030
`max_rows` (optional): Read `max_rows` lines of content after `skiprows` lines. A negative value results in reading all lines. A value of zero results in no lines to be read. The default value is -1.
3131

32+
`fmt` (optional): Fortran format specifier for the text read. Defaults to the write format for the data type. Setting fmt='*' will specify list directed read.
33+
34+
35+
3236
### Return value
3337

3438
Returns an allocated rank-2 `array` with the content of `filename`.

example/io/example_loadtxt.f90

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,4 +3,7 @@ program example_loadtxt
33
implicit none
44
real, allocatable :: x(:, :)
55
call loadtxt('example.dat', x)
6+
7+
! Can also use list directed format if the default read fails.
8+
call loadtxt('example.dat', x, fmt='*')
69
end program example_loadtxt

src/stdlib_io.fypp

Lines changed: 49 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -81,7 +81,7 @@ module stdlib_io
8181
contains
8282

8383
#:for k1, t1 in KINDS_TYPES
84-
subroutine loadtxt_${t1[0]}$${k1}$(filename, d, skiprows, max_rows)
84+
subroutine loadtxt_${t1[0]}$${k1}$(filename, d, skiprows, max_rows, fmt)
8585
!! version: experimental
8686
!!
8787
!! Loads a 2D array from a text file.
@@ -100,6 +100,8 @@ contains
100100
!! A value of zero results in no lines to be read.
101101
!! The default value is -1.
102102
integer, intent(in), optional :: max_rows
103+
character(len=*), intent(in), optional :: fmt
104+
character(len=:), allocatable :: fmt_
103105
!!
104106
!! Example
105107
!! -------
@@ -143,15 +145,52 @@ contains
143145
read(s, *)
144146
end do
145147

146-
do i = 1, max_rows_
147-
#:if 'real' in t1
148-
read(s, "(*"//FMT_REAL_${k1}$(1:len(FMT_REAL_${k1}$)-1)//",1x))") d(i, :)
149-
#:elif 'complex' in t1
150-
read(s, "(*"//FMT_COMPLEX_${k1}$(1:len(FMT_COMPLEX_${k1}$)-1)//",1x))") d(i, :)
151-
#:else
152-
read(s, *) d(i, :)
153-
#:endif
154-
end do
148+
#:if 'real' in t1
149+
! Default to format used for savetxt if fmt not specified.
150+
fmt_ = optval(fmt, "(*"//FMT_REAL_${k1}$(1:len(FMT_REAL_${k1}$)-1)//",1x))")
151+
152+
if ( fmt_ == '*' ) then
153+
! Use list directed read if user has specified fmt='*'
154+
do i = 1, max_rows_
155+
read (s,*) d(i, :)
156+
enddo
157+
else
158+
! Otherwise pass default or user specified fmt string.
159+
do i = 1, max_rows_
160+
read (s,fmt_) d(i, :)
161+
enddo
162+
endif
163+
#:elif 'complex' in t1
164+
! Default to format used for savetxt if fmt not specified.
165+
fmt_ = optval(fmt, "(*"//FMT_COMPLEX_${k1}$(1:len(FMT_COMPLEX_${k1}$)-1)//",1x))")
166+
if ( fmt_ == '*' ) then
167+
! Use list directed read if user has specified fmt='*'
168+
do i = 1, max_rows_
169+
read (s,*) d(i, :)
170+
enddo
171+
else
172+
! Otherwise pass default or user specified fmt string.
173+
do i = 1, max_rows_
174+
read (s,fmt_) d(i, :)
175+
enddo
176+
endif
177+
#:else
178+
! Default to list directed for integer
179+
fmt_ = optval(fmt, "*")
180+
! Use list directed read if user has specified fmt='*'
181+
if ( fmt_ == '*' ) then
182+
do i = 1, max_rows_
183+
read (s,*) d(i, :)
184+
enddo
185+
else
186+
! Otherwise pass default user specified fmt string.
187+
do i = 1, max_rows_
188+
read (s,fmt_) d(i, :)
189+
enddo
190+
endif
191+
192+
#:endif
193+
155194
close(s)
156195

157196
end subroutine loadtxt_${t1[0]}$${k1}$

test/io/test_loadtxt.f90

Lines changed: 65 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -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

Comments
 (0)