Skip to content

Commit 1b8ca1b

Browse files
committed
Add getline to read whole line from formatted unit
1 parent ce9c234 commit 1b8ca1b

File tree

6 files changed

+204
-1
lines changed

6 files changed

+204
-1
lines changed

doc/specs/stdlib_io.md

+48
Original file line numberDiff line numberDiff line change
@@ -223,3 +223,51 @@ program demo_savenpy
223223
call save_npy('example.npy', x)
224224
end program demo_savenpy
225225
```
226+
227+
## `getline`
228+
229+
### Status
230+
231+
Experimental
232+
233+
### Description
234+
235+
Read a whole line from a formatted unit into a string variable
236+
237+
### Syntax
238+
239+
`call [[stdlib_io(module):getline(interface)]](unit, line[, iostat][, iomsg])`
240+
241+
### Arguments
242+
243+
`unit`: Formatted input unit.
244+
This argument is `intent(in)`.
245+
246+
`line`: Deferred length character or `string_type` variable.
247+
This argument is `intent(out)`.
248+
249+
`iostat`: Default integer, contains status of reading from unit, zero in case of success.
250+
It is an optional argument, in case not present the program will halt for non-zero status.
251+
This argument is `intent(out)`.
252+
253+
`iomsg`: Deferred length character value, contains error message in case `iostat` is non-zero.
254+
It is an optional argument, error message will be dropped if not present.
255+
This argument is `intent(out)`.
256+
257+
### Example
258+
259+
```fortran
260+
program demo_getline
261+
use, intrinsic :: iso_fortran_env, only : input_unit, output_unit
262+
use stdlib_io, only: getline
263+
implicit none
264+
character(len=:), allocatable :: line
265+
integer :: stat
266+
267+
call getline(input_unit, line, stat)
268+
do while(stat == 0)
269+
write(output_unit, '(a)') line
270+
call getline(input_unit, line, stat)
271+
end do
272+
end program demo_getline
273+
```

src/Makefile.manual

+1
Original file line numberDiff line numberDiff line change
@@ -91,6 +91,7 @@ stdlib_io.o: \
9191
stdlib_error.o \
9292
stdlib_optval.o \
9393
stdlib_kinds.o \
94+
stdlib_string_type.o \
9495
stdlib_ascii.o
9596
stdlib_io_npy.o: \
9697
stdlib_kinds.o

src/stdlib_io.fypp

+65-1
Original file line numberDiff line numberDiff line change
@@ -11,10 +11,11 @@ module stdlib_io
1111
use stdlib_error, only: error_stop
1212
use stdlib_optval, only: optval
1313
use stdlib_ascii, only: is_blank
14+
use stdlib_string_type, only : string_type
1415
implicit none
1516
private
1617
! Public API
17-
public :: loadtxt, savetxt, open
18+
public :: loadtxt, savetxt, open, getline
1819

1920
! Private API that is exposed so that we can test it in tests
2021
public :: parse_mode
@@ -31,6 +32,14 @@ module stdlib_io
3132
FMT_COMPLEX_XDP = '(*(es26.18e3,1x,es26.18e3))', &
3233
FMT_COMPLEX_QP = '(*(es44.35e4,1x,es44.35e4))'
3334

35+
!> Version: experimental
36+
!>
37+
!> Read a whole line from a formatted unit into a string variable
38+
interface getline
39+
module procedure :: getline_char
40+
module procedure :: getline_string
41+
end interface getline
42+
3443
interface loadtxt
3544
!! version: experimental
3645
!!
@@ -331,4 +340,59 @@ contains
331340

332341
end function parse_mode
333342

343+
!> Version: experimental
344+
!>
345+
!> Read a whole line from a formatted unit into a deferred length character variable
346+
subroutine getline_char(unit, line, iostat, iomsg)
347+
!> Formatted IO unit
348+
integer, intent(in) :: unit
349+
!> Line to read
350+
character(len=:), allocatable, intent(out) :: line
351+
!> Status of operation
352+
integer, intent(out), optional :: iostat
353+
!> Error message
354+
character(len=:), allocatable, optional :: iomsg
355+
356+
integer, parameter :: bufsize = 512
357+
character(len=bufsize) :: buffer, msg
358+
integer :: chunk, stat
359+
360+
allocate(character(len=0) :: line)
361+
do
362+
read(unit, '(a)', advance='no', iostat=stat, iomsg=msg, size=chunk) buffer
363+
if (stat > 0) exit
364+
line = line // buffer(:chunk)
365+
if (stat < 0) then
366+
if (is_iostat_eor(stat)) stat = 0
367+
exit
368+
end if
369+
end do
370+
371+
if (stat /= 0 .and. present(iomsg)) iomsg = trim(msg)
372+
if (present(iostat)) then
373+
iostat = stat
374+
else if (stat /= 0) then
375+
call error_stop(trim(msg))
376+
end if
377+
end subroutine getline_char
378+
379+
!> Version: experimental
380+
!>
381+
!> Read a whole line from a formatted unit into a string variable
382+
subroutine getline_string(unit, line, iostat, iomsg)
383+
!> Formatted IO unit
384+
integer, intent(in) :: unit
385+
!> Line to read
386+
type(string_type), intent(out) :: line
387+
!> Status of operation
388+
integer, intent(out), optional :: iostat
389+
!> Error message
390+
character(len=:), allocatable, optional :: iomsg
391+
392+
character(len=:), allocatable :: buffer
393+
394+
call getline(unit, buffer, iostat, iomsg)
395+
line = string_type(buffer)
396+
end subroutine getline_string
397+
334398
end module stdlib_io

src/tests/io/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ ADDTEST(savetxt_qp)
1313
set_tests_properties(loadtxt_qp PROPERTIES LABELS quadruple_precision)
1414
set_tests_properties(savetxt_qp PROPERTIES LABELS quadruple_precision)
1515

16+
ADDTEST(getline)
1617
ADDTEST(npy)
1718
ADDTEST(open)
1819
ADDTEST(parse_mode)

src/tests/io/Makefile.manual

+1
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@ SRCGEN = $(SRCFYPP:.fypp=.f90)
66

77
PROGS_SRC = test_loadtxt.f90 \
88
test_savetxt.f90 \
9+
test_getline.f90 \
910
test_npy.f90 \
1011
test_parse_mode.f90 \
1112
test_open.f90 \

src/tests/io/test_getline.f90

+88
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,88 @@
1+
module test_getline
2+
use stdlib_io, only : getline
3+
use stdlib_string_type, only : string_type, len
4+
use testdrive, only : new_unittest, unittest_type, error_type, check
5+
implicit none
6+
private
7+
8+
public :: collect_getline
9+
10+
contains
11+
12+
!> Collect all exported unit tests
13+
subroutine collect_getline(testsuite)
14+
!> Collection of tests
15+
type(unittest_type), allocatable, intent(out) :: testsuite(:)
16+
17+
testsuite = [ &
18+
new_unittest("read-char", test_read_char), &
19+
new_unittest("read-string", test_read_string) &
20+
]
21+
end subroutine collect_getline
22+
23+
subroutine test_read_char(error)
24+
!> Error handling
25+
type(error_type), allocatable, intent(out) :: error
26+
27+
integer :: io, i, stat
28+
character(len=:), allocatable :: line
29+
30+
open(newunit=io, status="scratch")
31+
write(io, "(a)") repeat("abc", 10), repeat("def", 100), repeat("ghi", 1000)
32+
rewind(io)
33+
34+
do i = 1, 3
35+
call getline(io, line, stat)
36+
call check(error, stat)
37+
call check(error, len(line), 3*10**i)
38+
end do
39+
close(io)
40+
end subroutine test_read_char
41+
42+
subroutine test_read_string(error)
43+
!> Error handling
44+
type(error_type), allocatable, intent(out) :: error
45+
46+
integer :: io, i, stat
47+
type(string_type) :: line
48+
49+
open(newunit=io, status="scratch")
50+
write(io, "(a)") repeat("abc", 10), repeat("def", 100), repeat("ghi", 1000)
51+
rewind(io)
52+
53+
do i = 1, 3
54+
call getline(io, line, stat)
55+
call check(error, stat)
56+
call check(error, len(line), 3*10**i)
57+
end do
58+
close(io)
59+
end subroutine test_read_string
60+
61+
end module test_getline
62+
63+
64+
program tester
65+
use, intrinsic :: iso_fortran_env, only : error_unit
66+
use testdrive, only : run_testsuite, new_testsuite, testsuite_type
67+
use test_getline, only : collect_getline
68+
implicit none
69+
integer :: stat, is
70+
type(testsuite_type), allocatable :: testsuites(:)
71+
character(len=*), parameter :: fmt = '("#", *(1x, a))'
72+
73+
stat = 0
74+
75+
testsuites = [ &
76+
new_testsuite("getline", collect_getline) &
77+
]
78+
79+
do is = 1, size(testsuites)
80+
write(error_unit, fmt) "Testing:", testsuites(is)%name
81+
call run_testsuite(testsuites(is)%collect, error_unit, stat)
82+
end do
83+
84+
if (stat > 0) then
85+
write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
86+
error stop
87+
end if
88+
end program

0 commit comments

Comments
 (0)