Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
49 changes: 49 additions & 0 deletions doc/specs/stdlib_io.md
Original file line number Diff line number Diff line change
Expand Up @@ -246,6 +246,55 @@ Read a whole line from a formatted unit into a string variable
```fortran
{!example/io/example_get_line.f90!}
```
## `input` — read a line from standard input

### Status

Experimental

### Description

Reads a line from standard input, optionally displaying a prompt.

The function returns the input as an allocatable character string.
Trailing spaces and tabs are preserved.
No numeric conversion is performed.

### Syntax

`line = ` [[stdlib_io(module):input(function)]] `([prompt][, iostat][, iomsg])`

### Arguments

`prompt` (optional):
A `character` scalar containing a prompt to be displayed before reading input.
This argument is `intent(in)`.

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

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

### Return value

Returns a deferred-length allocatable `character` variable containing the input line.

### Notes

- Trailing spaces and tabs are preserved
- No type conversion is performed
- To convert to numbers, use `to_num` from `stdlib_string_to_num`

### Example

```fortran
{!example/io/example_input.f90!}
```

## Formatting constants

Expand Down
10 changes: 10 additions & 0 deletions example/io/example_input.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
program example_input
use stdlib_io, only : input
implicit none(type, external)

character(len=:), allocatable :: name

name = input("Enter your name: ")
print *, "Hello:", name

end program example_input
42 changes: 40 additions & 2 deletions src/stdlib_io.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module stdlib_io
!! Provides a support for file handling
!! ([Specification](../page/specs/stdlib_io.html))

use, intrinsic :: iso_fortran_env, only : input_unit
use, intrinsic :: iso_fortran_env, only : input_unit, output_unit
use stdlib_kinds, only: sp, dp, xdp, qp, &
int8, int16, int32, int64
use stdlib_error, only: error_stop, state_type, STDLIB_IO_ERROR
Expand All @@ -16,7 +16,7 @@ module stdlib_io
implicit none
private
! Public API
public :: loadtxt, savetxt, open, get_line, get_file
public :: loadtxt, savetxt, open, get_line, get_file, input

!! version: experimental
!!
Expand Down Expand Up @@ -82,6 +82,13 @@ module stdlib_io
module procedure :: get_line_input_string
end interface get_line

!> Version: experimental
!>
!> Read a line from standard input with an optional prompt
interface input
module procedure :: input_char
end interface input

interface loadtxt
!! version: experimental
!!
Expand Down Expand Up @@ -597,6 +604,37 @@ contains
call get_line(input_unit, line, iostat, iomsg)
end subroutine get_line_input_char

!> Version: experimental
!>
!> Read a line from standard input with an optional prompt.
!!
!! - Preserves trailing whitespace
!! - Returns allocatable character string
!! - Does not perform any type conversion; the input is returned as character data
!! - If `iostat` is present, errors are reported via `iostat`/`iomsg` instead of triggering `error_stop`
function input_char(prompt, iostat, iomsg) result(line)
character(len=*), intent(in), optional :: prompt
integer, intent(out), optional :: iostat
character(len=:), allocatable, optional :: iomsg
character(len=:), allocatable :: line

integer :: stat

! Print prompt without newline
if (present(prompt)) then
write(output_unit, '(a)', advance='no') prompt
end if

! Read line from standard input
call get_line_input_char(line, stat, iomsg)

if (present(iostat)) then
iostat = stat
else if (stat /= 0) then
call error_stop("input: error reading from standard input")
end if
end function input_char

!> Version: experimental
!>
!> Read a whole line from the standard input into a string variable
Expand Down
84 changes: 84 additions & 0 deletions test/test_input.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,84 @@
module test_input
use testdrive, only : new_unittest, unittest_type, error_type, check
use stdlib_io, only : input
implicit none
private
public :: collect

contains

subroutine collect(tests)
type(unittest_type), allocatable, intent(out) :: tests(:)

tests = [ &
new_unittest("input preserves whitespace", test_input_whitespace), &
new_unittest("input with prompt", test_input_prompt), &
new_unittest("input with iostat", test_input_iostat), &
new_unittest("input with iomsg", test_input_iomsg), &
new_unittest("input without optional args", test_input_no_args) &
]
end subroutine collect


subroutine test_input_whitespace(error)
type(error_type), allocatable, intent(out) :: error
character(len=:), allocatable :: s

call feed_stdin(" abc ")
s = input()
call assert_equal(error, s, " abc ")
end subroutine test_input_whitespace


subroutine test_input_prompt(error)
type(error_type), allocatable, intent(out) :: error
character(len=:), allocatable :: s

call write_test_input("abc")
s = input("Enter value: ")
call assert_equal(error, s, "abc")
end subroutine test_input_prompt


subroutine test_input_iostat(error)
type(error_type), allocatable, intent(out) :: error
character(len=:), allocatable :: s
integer :: ios

call write_test_input("abc")
s = input(iostat=ios)
call assert_equal(error, ios, 0)
call assert_equal(error, s, "abc")
end subroutine test_input_iostat


subroutine test_input_iomsg(error)
type(error_type), allocatable, intent(out) :: error
character(len=:), allocatable :: s
character(len=:), allocatable :: msg

call write_test_input("abc")
s = input(iomsg=msg)
call assert_equal(error, s, "abc")
end subroutine test_input_iomsg


subroutine test_input_no_args(error)
type(error_type), allocatable, intent(out) :: error
character(len=:), allocatable :: s

call write_test_input("abc")
s = input()
call assert_equal(error, s, "abc")
end subroutine test_input_no_args

end module test_input


program run_test_input
use testdrive, only : run_testsuite
use test_input, only : collect
implicit none

call run_testsuite(collect)
end program run_test_input