Skip to content

Commit a8da52a

Browse files
committed
RC 1
Initial commit with src additions, added a test and example and updated docs.
1 parent b5b86a7 commit a8da52a

File tree

4 files changed

+152
-7
lines changed

4 files changed

+152
-7
lines changed

doc/specs/stdlib_io.md

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -6,36 +6,37 @@ title: io
66

77
[TOC]
88

9-
## `loadtxt` - load a 2D array from a text file
9+
## `loadtxt` - load a 2D array or 1D character array from a text file
1010

1111
### Status
1212

1313
Experimental
1414

1515
### Description
16-
Loads a rank-2 `array` from a text file.
16+
Loads a rank-2 `array` or rank-1 `character array` from a text file.
1717

1818
### Syntax
1919

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

2222
### Arguments
2323

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

26-
`array`: Shall be an allocatable rank-2 array of type `real`, `complex` or `integer`.
26+
`array`: Shall be an allocatable rank-2 array of type `real`, `complex` or `integer` or a allocatable rank-1 `character` array.
2727

2828
`skiprows` (optional): Skip the first `skiprows` lines. If skipping more rows than present, a 0-sized array will be returned. The default is 0.
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.
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. Valid only for `real`, `complex` and `integer`.
3333

34+
`skip_blank_lines` (optional): Will ignore blank lines in the text file. Valid only for `character` array.
3435

3536

3637
### Return value
3738

38-
Returns an allocated rank-2 `array` with the content of `filename`.
39+
Returns an allocated rank-2 `array` with the content of `filename`, or a rank-1 `character` array where the length is the longest line of the file.
3940

4041
### Example
4142

example/io/example_loadtxt.f90

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,8 +2,12 @@ program example_loadtxt
22
use stdlib_io, only: loadtxt
33
implicit none
44
real, allocatable :: x(:, :)
5+
character(len=:), allocatable :: text(:)
56
call loadtxt('example.dat', x)
67

78
! Can also use list directed format if the default read fails.
89
call loadtxt('example.dat', x, fmt='*')
10+
11+
! Load as a character array. Character len will be equal to the largest line length.
12+
call loadtxt('example.dat', text)
913
end program example_loadtxt

src/stdlib_io.fypp

Lines changed: 114 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -66,6 +66,7 @@ module stdlib_io
6666
#:for k1, t1 in KINDS_TYPES
6767
module procedure loadtxt_${t1[0]}$${k1}$
6868
#:endfor
69+
module procedure :: loadtxt_char
6970
end interface loadtxt
7071

7172
interface savetxt
@@ -192,6 +193,119 @@ contains
192193
end subroutine loadtxt_${t1[0]}$${k1}$
193194
#:endfor
194195

196+
subroutine loadtxt_char(filename, d, skiprows, max_rows, skip_blank_lines)
197+
!!
198+
!! Loads a text file into a 1D character array.
199+
!!
200+
character(len=*), intent(in) :: filename
201+
character(len=:), intent(out), allocatable :: d(:)
202+
integer, intent(in), optional :: skiprows, max_rows
203+
logical, intent(in), optional :: skip_blank_lines
204+
205+
logical :: skip_blank_lines_, read_line
206+
207+
integer :: i, u, len_text, max_line_length, line_length, start_pos, end_pos, &
208+
current_line, next_line_pos, step, max_rows_, skiprows_
209+
210+
character(len=:), allocatable :: text
211+
212+
! Set default optional values
213+
skiprows_ = optval(skiprows, 0)
214+
max_rows_ = optval(max_rows, -1)
215+
skip_blank_lines_ = optval(skip_blank_lines, .false.)
216+
217+
!! Open and store all of file contents.
218+
open (newunit=u, file=filename, action='read', form='unformatted', access='stream')
219+
inquire(unit=u, size=len_text) ! Get total character count of file.
220+
allocate(character(len=len_text) :: text)
221+
read(u) text
222+
close(u)
223+
224+
! Loop through file twice.
225+
! step = 1 loop will get line count, max line size and allocate character array.
226+
! step = 2 will fill the array.
227+
do step = 1, 2
228+
max_line_length = 0
229+
! Will skip skiprow lines if specified, since will only read line if current_line is positive.
230+
current_line = -skiprows_
231+
next_line_pos = 1
232+
do while (next_line_pos > 0)
233+
234+
start_pos = next_line_pos
235+
236+
! Search text starting at start_pos for end of line. end_pos will exclude CRLR or LR characters.
237+
! next line idx is the start of the next line. Will be 0 if last line in text.
238+
call get_line(text, start_pos, end_pos, next_line_pos)
239+
240+
! Check for and skip blank lines if requested.
241+
read_line = .true.
242+
if (skip_blank_lines_) then
243+
if (len_trim(text(start_pos:end_pos)) == 0) read_line = .false.
244+
endif
245+
246+
if (read_line) then
247+
current_line = current_line + 1
248+
if (step == 1) then
249+
line_length = end_pos - start_pos + 1
250+
if ((line_length > max_line_length) .and. (current_line > 0)) max_line_length = line_length
251+
else
252+
if (current_line > 0) d(current_line) = text(start_pos:end_pos)
253+
endif
254+
endif
255+
256+
if ((max_rows_ >= 0) .and. (current_line == max_rows_)) exit ! Check max_row input if user has specified that.
257+
enddo
258+
259+
if (step == 1) then
260+
! Allocate character array with max line size and line count.
261+
! If skip rows higher than lines found, allocate to size 0 array.
262+
allocate( character(max_line_length) :: d(max(0,current_line)))
263+
endif
264+
enddo
265+
266+
contains
267+
268+
pure subroutine get_line(text, start_idx, end_idx, next_line_idx)
269+
! Search ftext for line returns. Start_idx:end_idx will be the character variables of the line.
270+
! next_line_idx is the start of the next line. Will be 0 if last line in text.
271+
character(len=*), intent(in) :: text
272+
integer, intent(in) :: start_idx
273+
integer, intent(out) :: end_idx, next_line_idx
274+
275+
integer :: idx, ascii_idx
276+
277+
idx = start_idx
278+
279+
!If no line ending found, will return end pos of text and next_line_idx = 0.
280+
next_line_idx = 0
281+
end_idx = len(text)
282+
283+
do while (idx <= len(text))
284+
!! Find line end
285+
! Look for either CR or LR
286+
ascii_idx = iachar(text(idx:idx))
287+
288+
if (ascii_idx == 13) then
289+
! Found CR return. Check for LR
290+
if (iachar(text(idx+1:idx+1)) == 10) then
291+
end_idx = idx - 1
292+
next_line_idx = idx + 2
293+
return
294+
endif
295+
296+
! Check for standalone LR
297+
elseif (ascii_idx == 10) then
298+
end_idx = idx - 1
299+
next_line_idx = idx + 1
300+
return
301+
endif
302+
303+
! Go to next line
304+
idx = idx + 1
305+
enddo
306+
end subroutine get_line
307+
end subroutine loadtxt_char
308+
195309

196310
#:for k1, t1 in KINDS_TYPES
197311
subroutine savetxt_${t1[0]}$${k1}$(filename, d)

test/io/test_loadtxt.f90

Lines changed: 27 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,8 @@ subroutine collect_loadtxt(testsuite)
2222
new_unittest("loadtxt_dp_max_skip", test_loadtxt_dp_max_skip), &
2323
new_unittest("loadtxt_dp_huge", test_loadtxt_dp_huge), &
2424
new_unittest("loadtxt_dp_tiny", test_loadtxt_dp_tiny), &
25-
new_unittest("loadtxt_complex", test_loadtxt_complex) &
25+
new_unittest("loadtxt_complex", test_loadtxt_complex), &
26+
new_unittest("loadtxt_char", test_loadtxt_char) &
2627
]
2728

2829
end subroutine collect_loadtxt
@@ -275,6 +276,31 @@ subroutine test_loadtxt_complex(error)
275276
end do
276277

277278
end subroutine test_loadtxt_complex
279+
280+
subroutine test_loadtxt_char(error)
281+
!> Error handling
282+
type(error_type), allocatable, intent(out) :: error
283+
character(len=5) :: input(3)
284+
character(len=:), allocatable :: expected(:)
285+
integer :: u, n
286+
287+
open(newunit=u, file="test_char.txt")
288+
write(u,'(A)') 'skipped'
289+
write(u,'(A)') 'skipped'
290+
write(u,'(A)') ' '
291+
write(u,'(A)') 'line'
292+
write(u,'(A)') 'line'
293+
write(u,'(A)') 'char length should be 23'
294+
write(u,'(A)') 'skipped'
295+
write(u,'(A)') 'skipped'
296+
close(u)
297+
298+
call loadtxt('test_char.txt', expected, skip_blank_lines=.true., skiprows=2, max_rows=3)
299+
300+
call check(error, size(expected) == 3,'loadtxt_char returns incorrect line count.')
301+
call check(error, len(expected) == 24,'loadtxt_char returns incorrect line size.')
302+
303+
end subroutine test_loadtxt_char
278304

279305
end module test_loadtxt
280306

0 commit comments

Comments
 (0)