Skip to content

Commit bae6be5

Browse files
awvwgkmilancurcic
andauthored
Add getline to read whole line from formatted unit (#597)
Co-authored-by: Milan Curcic <[email protected]>
1 parent 2601bf1 commit bae6be5

File tree

7 files changed

+332
-1
lines changed

7 files changed

+332
-1
lines changed

Diff for: CHANGELOG.md

+3
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,9 @@ Features available from the latest git source
1010
- new module `stdlib_version`
1111
[#579](https://github.com/fortran-lang/stdlib/pull/579)
1212
- new procedure `get_stdlib_version`
13+
- update module `stdlib_io`
14+
[597](https://github.com/fortran-lang/stdlib/pull/597)
15+
- new procedure `getline`
1316
- new module `stdlib_io_npy`
1417
[#581](https://github.com/fortran-lang/stdlib/pull/581)
1518
- new procedures `save_npy`, `load_npy`

Diff for: doc/specs/stdlib_io.md

+50
Original file line numberDiff line numberDiff line change
@@ -223,3 +223,53 @@ 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+
`call [[stdlib_io(module):getline(interface)]] (line[, iostat][, iomsg])`
241+
242+
### Arguments
243+
244+
`unit`: Formatted input unit.
245+
This argument is `intent(in)`.
246+
If `unit` is not specified standard input is used.
247+
248+
`line`: Deferred length character or `string_type` variable.
249+
This argument is `intent(out)`.
250+
251+
`iostat`: Default integer, contains status of reading from unit, zero in case of success.
252+
It is an optional argument, in case not present the program will halt for non-zero status.
253+
This argument is `intent(out)`.
254+
255+
`iomsg`: Deferred length character value, contains error message in case `iostat` is non-zero.
256+
It is an optional argument, error message will be dropped if not present.
257+
This argument is `intent(out)`.
258+
259+
### Example
260+
261+
```fortran
262+
program demo_getline
263+
use, intrinsic :: iso_fortran_env, only : input_unit, output_unit
264+
use stdlib_io, only: getline
265+
implicit none
266+
character(len=:), allocatable :: line
267+
integer :: stat
268+
269+
call getline(input_unit, line, stat)
270+
do while(stat == 0)
271+
write(output_unit, '(a)') line
272+
call getline(input_unit, line, stat)
273+
end do
274+
end program demo_getline
275+
```

Diff for: src/Makefile.manual

+1
Original file line numberDiff line numberDiff line change
@@ -95,6 +95,7 @@ stdlib_io.o: \
9595
stdlib_error.o \
9696
stdlib_optval.o \
9797
stdlib_kinds.o \
98+
stdlib_string_type.o \
9899
stdlib_ascii.o
99100
stdlib_io_npy.o: \
100101
stdlib_kinds.o

Diff for: src/stdlib_io.fypp

+107-1
Original file line numberDiff line numberDiff line change
@@ -6,15 +6,17 @@ module stdlib_io
66
!! Provides a support for file handling
77
!! ([Specification](../page/specs/stdlib_io.html))
88

9+
use, intrinsic :: iso_fortran_env, only : input_unit
910
use stdlib_kinds, only: sp, dp, xdp, qp, &
1011
int8, int16, int32, int64
1112
use stdlib_error, only: error_stop
1213
use stdlib_optval, only: optval
1314
use stdlib_ascii, only: is_blank
15+
use stdlib_string_type, only : string_type
1416
implicit none
1517
private
1618
! Public API
17-
public :: loadtxt, savetxt, open
19+
public :: loadtxt, savetxt, open, getline
1820

1921
! Private API that is exposed so that we can test it in tests
2022
public :: parse_mode
@@ -31,6 +33,16 @@ module stdlib_io
3133
FMT_COMPLEX_XDP = '(*(es26.18e3,1x,es26.18e3))', &
3234
FMT_COMPLEX_QP = '(*(es44.35e4,1x,es44.35e4))'
3335

36+
!> Version: experimental
37+
!>
38+
!> Read a whole line from a formatted unit into a string variable
39+
interface getline
40+
module procedure :: getline_char
41+
module procedure :: getline_string
42+
module procedure :: getline_input_char
43+
module procedure :: getline_input_string
44+
end interface getline
45+
3446
interface loadtxt
3547
!! version: experimental
3648
!!
@@ -331,4 +343,98 @@ contains
331343

332344
end function parse_mode
333345

346+
!> Version: experimental
347+
!>
348+
!> Read a whole line from a formatted unit into a deferred length character variable
349+
subroutine getline_char(unit, line, iostat, iomsg)
350+
!> Formatted IO unit
351+
integer, intent(in) :: unit
352+
!> Line to read
353+
character(len=:), allocatable, intent(out) :: line
354+
!> Status of operation
355+
integer, intent(out), optional :: iostat
356+
!> Error message
357+
character(len=:), allocatable, optional :: iomsg
358+
359+
integer, parameter :: bufsize = 4096
360+
character(len=bufsize) :: buffer, msg
361+
integer :: chunk, stat
362+
logical :: opened
363+
364+
if (unit /= -1) then
365+
inquire(unit=unit, opened=opened)
366+
else
367+
opened = .false.
368+
end if
369+
370+
if (opened) then
371+
open(unit=unit, pad="yes", iostat=stat, iomsg=msg)
372+
else
373+
stat = 1
374+
msg = "Unit is not connected"
375+
end if
376+
377+
line = ""
378+
do while (stat == 0)
379+
read(unit, '(a)', advance='no', iostat=stat, iomsg=msg, size=chunk) buffer
380+
if (stat > 0) exit
381+
line = line // buffer(:chunk)
382+
end do
383+
if (is_iostat_eor(stat)) stat = 0
384+
385+
if (stat /= 0 .and. present(iomsg)) iomsg = trim(msg)
386+
if (present(iostat)) then
387+
iostat = stat
388+
else if (stat /= 0) then
389+
call error_stop(trim(msg))
390+
end if
391+
end subroutine getline_char
392+
393+
!> Version: experimental
394+
!>
395+
!> Read a whole line from a formatted unit into a string variable
396+
subroutine getline_string(unit, line, iostat, iomsg)
397+
!> Formatted IO unit
398+
integer, intent(in) :: unit
399+
!> Line to read
400+
type(string_type), intent(out) :: line
401+
!> Status of operation
402+
integer, intent(out), optional :: iostat
403+
!> Error message
404+
character(len=:), allocatable, optional :: iomsg
405+
406+
character(len=:), allocatable :: buffer
407+
408+
call getline(unit, buffer, iostat, iomsg)
409+
line = string_type(buffer)
410+
end subroutine getline_string
411+
412+
!> Version: experimental
413+
!>
414+
!> Read a whole line from the standard input into a deferred length character variable
415+
subroutine getline_input_char(line, iostat, iomsg)
416+
!> Line to read
417+
character(len=:), allocatable, intent(out) :: line
418+
!> Status of operation
419+
integer, intent(out), optional :: iostat
420+
!> Error message
421+
character(len=:), allocatable, optional :: iomsg
422+
423+
call getline(input_unit, line, iostat, iomsg)
424+
end subroutine getline_input_char
425+
426+
!> Version: experimental
427+
!>
428+
!> Read a whole line from the standard input into a string variable
429+
subroutine getline_input_string(line, iostat, iomsg)
430+
!> Line to read
431+
type(string_type), intent(out) :: line
432+
!> Status of operation
433+
integer, intent(out), optional :: iostat
434+
!> Error message
435+
character(len=:), allocatable, optional :: iomsg
436+
437+
call getline(input_unit, line, iostat, iomsg)
438+
end subroutine getline_input_string
439+
334440
end module stdlib_io

Diff for: 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)

Diff for: 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 \

Diff for: src/tests/io/test_getline.f90

+169
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,169 @@
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+
new_unittest("pad-no", test_pad_no), &
21+
new_unittest("iostat-end", test_iostat_end), &
22+
new_unittest("closed-unit", test_closed_unit, should_fail=.true.), &
23+
new_unittest("no-unit", test_no_unit, should_fail=.true.) &
24+
]
25+
end subroutine collect_getline
26+
27+
subroutine test_read_char(error)
28+
!> Error handling
29+
type(error_type), allocatable, intent(out) :: error
30+
31+
integer :: io, i, stat
32+
character(len=:), allocatable :: line
33+
34+
open(newunit=io, status="scratch")
35+
write(io, "(a)") repeat("abc", 10), repeat("def", 100), repeat("ghi", 1000)
36+
rewind(io)
37+
38+
do i = 1, 3
39+
call getline(io, line, stat)
40+
call check(error, stat)
41+
if (allocated(error)) exit
42+
call check(error, len(line), 3*10**i)
43+
if (allocated(error)) exit
44+
end do
45+
close(io)
46+
end subroutine test_read_char
47+
48+
subroutine test_read_string(error)
49+
!> Error handling
50+
type(error_type), allocatable, intent(out) :: error
51+
52+
integer :: io, i, stat
53+
type(string_type) :: line
54+
55+
open(newunit=io, status="scratch")
56+
write(io, "(a)") repeat("abc", 10), repeat("def", 100), repeat("ghi", 1000)
57+
rewind(io)
58+
59+
do i = 1, 3
60+
call getline(io, line, stat)
61+
call check(error, stat)
62+
if (allocated(error)) exit
63+
call check(error, len(line), 3*10**i)
64+
if (allocated(error)) exit
65+
end do
66+
close(io)
67+
end subroutine test_read_string
68+
69+
subroutine test_pad_no(error)
70+
!> Error handling
71+
type(error_type), allocatable, intent(out) :: error
72+
73+
integer :: io, i, stat
74+
character(len=:), allocatable :: line
75+
76+
open(newunit=io, status="scratch", pad="no")
77+
write(io, "(a)") repeat("abc", 10), repeat("def", 100), repeat("ghi", 1000)
78+
rewind(io)
79+
80+
do i = 1, 3
81+
call getline(io, line, stat)
82+
call check(error, stat)
83+
if (allocated(error)) exit
84+
call check(error, len(line), 3*10**i)
85+
if (allocated(error)) exit
86+
end do
87+
close(io)
88+
end subroutine test_pad_no
89+
90+
subroutine test_iostat_end(error)
91+
use, intrinsic :: iso_fortran_env, only : iostat_end
92+
!> Error handling
93+
type(error_type), allocatable, intent(out) :: error
94+
95+
integer :: io, i, stat
96+
character(len=:), allocatable :: line
97+
98+
open(newunit=io, status="scratch")
99+
write(io, "(a)") repeat("abc", 10), repeat("def", 100), repeat("ghi", 1000)
100+
rewind(io)
101+
102+
do i = 1, 3
103+
call getline(io, line, stat)
104+
call check(error, stat)
105+
if (allocated(error)) exit
106+
call check(error, len(line), 3*10**i)
107+
if (allocated(error)) exit
108+
end do
109+
if (.not.allocated(error)) then
110+
call getline(io, line, stat)
111+
call check(error, stat, iostat_end)
112+
end if
113+
close(io)
114+
end subroutine test_iostat_end
115+
116+
subroutine test_closed_unit(error)
117+
!> Error handling
118+
type(error_type), allocatable, intent(out) :: error
119+
120+
integer :: io, stat
121+
character(len=:), allocatable :: line, msg
122+
123+
open(newunit=io, status="scratch")
124+
close(io)
125+
126+
call getline(io, line, stat, msg)
127+
call check(error, stat, msg)
128+
end subroutine test_closed_unit
129+
130+
subroutine test_no_unit(error)
131+
!> Error handling
132+
type(error_type), allocatable, intent(out) :: error
133+
134+
integer :: io, stat
135+
character(len=:), allocatable :: line, msg
136+
137+
io = -1
138+
call getline(io, line, stat, msg)
139+
call check(error, stat, msg)
140+
end subroutine test_no_unit
141+
142+
end module test_getline
143+
144+
145+
program tester
146+
use, intrinsic :: iso_fortran_env, only : error_unit
147+
use testdrive, only : run_testsuite, new_testsuite, testsuite_type
148+
use test_getline, only : collect_getline
149+
implicit none
150+
integer :: stat, is
151+
type(testsuite_type), allocatable :: testsuites(:)
152+
character(len=*), parameter :: fmt = '("#", *(1x, a))'
153+
154+
stat = 0
155+
156+
testsuites = [ &
157+
new_testsuite("getline", collect_getline) &
158+
]
159+
160+
do is = 1, size(testsuites)
161+
write(error_unit, fmt) "Testing:", testsuites(is)%name
162+
call run_testsuite(testsuites(is)%collect, error_unit, stat)
163+
end do
164+
165+
if (stat > 0) then
166+
write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
167+
error stop
168+
end if
169+
end program

0 commit comments

Comments
 (0)