Skip to content

Commit 3028a36

Browse files
MuellerSebivan-pi14NGiestasmilancurcic
authored
Feature: loadtxt skiprows and max_rows (#652)
* stdlib_io: add skiprows to loadtxt * Add test for skiprows in loadtxt * stdlib_io: add check for skiprows >= 0 * stdlib_io: add max_rows to loadtxt * Update src/stdlib_io.fypp Co-authored-by: Ivan Pribec <[email protected]> * loadtxt: Add test for max_rows * loadtxt: treat negative skiprows as 0 (numpy like) * stdlib_io: cut off skiprows * stdlib_io: docs for cut off skiprows * rename test in src/tests/io/test_loadtxt.f90 Co-authored-by: Ian Giestas Pauli <[email protected]> * update specs docs of loadtxt * Update doc/specs/stdlib_io.md Co-authored-by: Milan Curcic <[email protected]> * Update src/stdlib_io.fypp Co-authored-by: Milan Curcic <[email protected]> * loadtxt: determine number of columns from first line to be read * number_of_columns: bugfix for missing int Co-authored-by: Ivan Pribec <[email protected]> Co-authored-by: Ian Giestas Pauli <[email protected]> Co-authored-by: Milan Curcic <[email protected]>
1 parent 729d5d8 commit 3028a36

File tree

3 files changed

+65
-11
lines changed

3 files changed

+65
-11
lines changed

doc/specs/stdlib_io.md

+6-2
Original file line numberDiff line numberDiff line change
@@ -17,14 +17,18 @@ Loads a rank-2 `array` from a text file.
1717

1818
### Syntax
1919

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

2222
### Arguments
2323

2424
`filename`: Shall be a character expression containing the file name from which to load the rank-2 `array`.
2525

2626
`array`: Shall be an allocatable rank-2 array of type `real`, `complex` or `integer`.
2727

28+
`skiprows` (optional): Skip the first `skiprows` lines. If skipping more rows than present, a 0-sized array will be returned. The default is 0.
29+
30+
`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.
31+
2832
### Return value
2933

3034
Returns an allocated rank-2 `array` with the content of `filename`.
@@ -314,4 +318,4 @@ program demo_fmt_constants
314318
print FMT_COMPLEX_DP, c64 ! outputs: 1.0000000000000000E+002 0.0000000000000000E+000
315319
316320
end program demo_fmt_constants
317-
```
321+
```

src/stdlib_io.fypp

+35-9
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)
84+
subroutine loadtxt_${t1[0]}$${k1}$(filename, d, skiprows, max_rows)
8585
!! version: experimental
8686
!!
8787
!! Loads a 2D array from a text file.
@@ -93,6 +93,13 @@ contains
9393
character(len=*), intent(in) :: filename
9494
!! The array 'd' will be automatically allocated with the correct dimensions
9595
${t1}$, allocatable, intent(out) :: d(:,:)
96+
!! Skip the first `skiprows` lines. If skipping more rows than present, a 0-sized array will be returned. The default is 0.
97+
integer, intent(in), optional :: skiprows
98+
!! Read `max_rows` lines of content after `skiprows` lines.
99+
!! A negative value results in reading all lines.
100+
!! A value of zero results in no lines to be read.
101+
!! The default value is -1.
102+
integer, intent(in), optional :: max_rows
96103
!!
97104
!! Example
98105
!! -------
@@ -111,21 +118,32 @@ contains
111118
!! ...
112119
!!
113120
integer :: s
114-
integer :: nrow, ncol, i
121+
integer :: nrow, ncol, i, skiprows_, max_rows_
122+
123+
skiprows_ = max(optval(skiprows, 0), 0)
124+
max_rows_ = optval(max_rows, -1)
115125

116126
s = open(filename)
117127

128+
! determine number or rows
129+
nrow = number_of_rows(s)
130+
skiprows_ = min(skiprows_, nrow)
131+
if ( max_rows_ < 0 .or. max_rows_ > (nrow - skiprows_) ) max_rows_ = nrow - skiprows_
132+
118133
! determine number of columns
119-
ncol = number_of_columns(s)
134+
ncol = 0
135+
if ( skiprows_ < nrow ) ncol = number_of_columns(s, skiprows=skiprows_)
120136
#:if 'complex' in t1
121137
ncol = ncol / 2
122138
#:endif
123139

124-
! determine number or rows
125-
nrow = number_of_rows(s)
140+
allocate(d(max_rows_, ncol))
126141

127-
allocate(d(nrow, ncol))
128-
do i = 1, nrow
142+
do i = 1, skiprows_
143+
read(s, *)
144+
end do
145+
146+
do i = 1, max_rows_
129147
#:if 'real' in t1
130148
read(s, "(*"//FMT_REAL_${k1}$(1:len(FMT_REAL_${k1}$)-1)//",1x))") d(i, :)
131149
#:elif 'complex' in t1
@@ -179,17 +197,25 @@ contains
179197
#:endfor
180198

181199

182-
integer function number_of_columns(s)
200+
integer function number_of_columns(s, skiprows)
183201
!! version: experimental
184202
!!
185203
!! determine number of columns
186204
integer,intent(in) :: s
205+
integer, intent(in), optional :: skiprows
187206

188-
integer :: ios
207+
integer :: ios, skiprows_, i
189208
character :: c
190209
logical :: lastblank
191210

211+
skiprows_ = optval(skiprows, 0)
212+
192213
rewind(s)
214+
215+
do i = 1, skiprows_
216+
read(s, *)
217+
end do
218+
193219
number_of_columns = 0
194220
lastblank = .true.
195221
do

src/tests/io/test_loadtxt.f90

+24
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ subroutine collect_loadtxt(testsuite)
1919
new_unittest("loadtxt_sp_huge", test_loadtxt_sp_huge), &
2020
new_unittest("loadtxt_sp_tiny", test_loadtxt_sp_tiny), &
2121
new_unittest("loadtxt_dp", test_loadtxt_dp), &
22+
new_unittest("loadtxt_dp_max_skip", test_loadtxt_dp_max_skip), &
2223
new_unittest("loadtxt_dp_huge", test_loadtxt_dp_huge), &
2324
new_unittest("loadtxt_dp_tiny", test_loadtxt_dp_tiny), &
2425
new_unittest("loadtxt_complex", test_loadtxt_complex) &
@@ -134,6 +135,29 @@ subroutine test_loadtxt_dp(error)
134135
end subroutine test_loadtxt_dp
135136

136137

138+
subroutine test_loadtxt_dp_max_skip(error)
139+
!> Error handling
140+
type(error_type), allocatable, intent(out) :: error
141+
real(dp), allocatable :: input(:,:), expected(:,:)
142+
integer :: n, m
143+
144+
allocate(input(10,10))
145+
146+
do m = 0, 5
147+
do n = 1, 11
148+
call random_number(input)
149+
input = input - 0.5
150+
call savetxt('test_dp_max_skip.txt', input)
151+
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))
153+
deallocate(expected)
154+
if (allocated(error)) return
155+
end do
156+
end do
157+
158+
end subroutine test_loadtxt_dp_max_skip
159+
160+
137161
subroutine test_loadtxt_dp_huge(error)
138162
!> Error handling
139163
type(error_type), allocatable, intent(out) :: error

0 commit comments

Comments
 (0)