Skip to content

Commit fb7572b

Browse files
io: implement input() with tests and documentation (fixes #259)
1 parent 92516a4 commit fb7572b

File tree

4 files changed

+13
-16
lines changed

4 files changed

+13
-16
lines changed

doc/specs/stdlib_io.md

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -255,7 +255,6 @@ Experimental
255255
### Description
256256

257257
Reads a line from standard input, optionally displaying a prompt.
258-
This is similar to Python’s `input()` function.
259258

260259
The function returns the input as an allocatable character string.
261260
Trailing spaces and tabs are preserved.
@@ -268,16 +267,17 @@ No numeric conversion is performed.
268267
### Arguments
269268

270269
`prompt` (optional):
271-
A character expression containing a prompt to be displayed before reading input.
270+
A `character` scalar containing a prompt to be displayed before reading input.
272271
This argument is `intent(in)`.
273272

274273
`iostat` (optional):
275-
Default integer, contains status of reading from standard input.
276-
Zero indicates success.
274+
Default `integer` scalar that contains the status of reading from standard input.
275+
The value is zero if the operation succeeds; otherwise the value is non-zero.
276+
If this argument is not provided and an error occurs, an `error stop` is triggered.
277277
This argument is `intent(out)`.
278278

279279
`iomsg` (optional):
280-
Deferred-length character variable containing an error message if `iostat` is non-zero.
280+
Deferred-length `character` variable containing an error message if `iostat` is non-zero.
281281
This argument is `intent(out)`.
282282

283283
### Return value
@@ -288,7 +288,7 @@ Returns a deferred-length allocatable `character` variable containing the input
288288

289289
- Trailing spaces and tabs are preserved
290290
- No type conversion is performed
291-
- To convert to numbers, use `read(line, *)`
291+
- To convert to numbers, use `to_num` from `stdlib_string_to_num`
292292

293293
### Example
294294

example/io/example_input.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
program example_input
22
use stdlib_io, only : input
3-
implicit none
3+
implicit none(type, external)
44

55
character(len=:), allocatable :: name
66

src/stdlib_io.fypp

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ 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
9+
use, intrinsic :: iso_fortran_env, only : input_unit, output_unit
1010
use stdlib_kinds, only: sp, dp, xdp, qp, &
1111
int8, int16, int32, int64
1212
use stdlib_error, only: error_stop, state_type, STDLIB_IO_ERROR
@@ -607,14 +607,12 @@ contains
607607
!> Version: experimental
608608
!>
609609
!> Read a line from standard input with an optional prompt.
610-
!! Similar to Python's input().
611610
!!
612611
!! - Preserves trailing whitespace
613612
!! - Returns allocatable character string
614-
!! - Does not perform type conversion
615-
!! - Does not stop on error unless caller chooses to
613+
!! - Does not perform any type conversion; the input is returned as character data
614+
!! - If `iostat` is present, errors are reported via `iostat`/`iomsg` instead of triggering `error_stop`
616615
function input_char(prompt, iostat, iomsg) result(line)
617-
use, intrinsic :: iso_fortran_env, only : output_unit
618616
character(len=*), intent(in), optional :: prompt
619617
integer, intent(out), optional :: iostat
620618
character(len=:), allocatable, optional :: iomsg
@@ -627,7 +625,7 @@ contains
627625
write(output_unit, '(a)', advance='no') prompt
628626
end if
629627

630-
! Read line from stdin
628+
! Read line from standard input
631629
call get_line_input_char(line, stat, iomsg)
632630

633631
if (present(iostat)) then

test/test_input.f90

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
module test_input
2-
use testdrive, only : new_unittest, unittest_type, error_type, assert_equal
2+
use testdrive, only : new_unittest, unittest_type, error_type, check
33
use stdlib_io, only : input
4-
use stdlib_test_utils, only : write_test_input
54
implicit none
65
private
76
public :: collect
@@ -25,7 +24,7 @@ subroutine test_input_whitespace(error)
2524
type(error_type), allocatable, intent(out) :: error
2625
character(len=:), allocatable :: s
2726

28-
call write_test_input(" abc ")
27+
call feed_stdin(" abc ")
2928
s = input()
3029
call assert_equal(error, s, " abc ")
3130
end subroutine test_input_whitespace

0 commit comments

Comments
 (0)