diff --git a/doc/specs/stdlib_io.md b/doc/specs/stdlib_io.md index 40cb2b426..f86a02ac9 100644 --- a/doc/specs/stdlib_io.md +++ b/doc/specs/stdlib_io.md @@ -49,7 +49,7 @@ Experimental ### Description -Returns the unit number of a file opened to read, to write, or to read and write. The file might be a text file or a binary file. All files are opened using a streamed access. +Returns the unit number of a file opened to read, to write, or to read and write. The file might be a text file or a binary file. All files are opened using a streamed access by default. ### Syntax @@ -71,9 +71,12 @@ Returns the unit number of a file opened to read, to write, or to read and write | `'+'` | open for updating (reading and writing) | | `'b'` | binary mode | | `'t'` | text mode (default) | +| `'u'` | sequential access | +| `'d'` | direct access | +| `'s'` | stream access (default) | -The default `mode` is `'rt'` (i.e. open for reading a text file). The `mode` may include one of the four different methods for opening a file (i.e., `'r'`, `'w'`, `'x'`, and `'a'`). These four methods can be associated with the character `'+'` to open the file for updating. In addition, it can be specified if the file should be handled as a binary file (`'b'`) or a text file (`'t'`). +The default `mode` is `'rts'` (i.e. open for reading a text file). The `mode` may include one of the four different methods for opening a file (i.e., `'r'`, `'w'`, `'x'`, and `'a'`). These four methods can be associated with the character `'+'` to open the file for updating. In addition, it can be specified if the file should be handled as a binary file (`'b'`) or a text file (`'t'`). `iostat` (optional): Shall be a scalar of type `integer` that receives the error status of `open`, if provided. If no error exists, `iostat` is zero. diff --git a/src/stdlib_io.fypp b/src/stdlib_io.fypp index dcacaa644..ee3e018fd 100644 --- a/src/stdlib_io.fypp +++ b/src/stdlib_io.fypp @@ -211,7 +211,7 @@ contains character(*), intent(in), optional :: mode integer, intent(out), optional :: iostat - character(3) :: mode_ + character(4) :: mode_ character(:),allocatable :: action_, position_, status_, access_, form_ @@ -263,7 +263,11 @@ contains call error_stop("Unsupported mode: "//mode_(3:3)) end select - access_ = 'stream' + select case (mode_(4:4)) + case('u'); access_ = 'sequential' + case('d'); access_ = 'direct' + case('s'); access_ = 'stream' + end select if (present(iostat)) then open(newunit=u, file=filename, & @@ -278,14 +282,14 @@ contains end function open - character(3) function parse_mode(mode) result(mode_) + character(4) function parse_mode(mode) result(mode_) character(*), intent(in) :: mode integer :: i character(:),allocatable :: a - logical :: lfirst(3) + logical :: lfirst(4) - mode_ = 'r t' + mode_ = 'r ts' if (len_trim(mode) == 0) return a=trim(adjustl(mode)) @@ -303,6 +307,9 @@ contains else if (lfirst(3) .and. (a(i:i) == 't' .or. a(i:i) == 'b')) then mode_(3:3) = a(i:i) lfirst(3)=.false. + else if (lfirst(4) .and. (a(i:i) == 'u' .or. a(i:i) == 'd' .or. a(i:i) == 's')) then + mode_(4:4) = a(i:i) + lfirst(4)=.false. else if (a(i:i) == ' ') then cycle else if(any(.not.lfirst)) then diff --git a/src/tests/io/test_open.f90 b/src/tests/io/test_open.f90 index c639c6119..8a5cfc3e5 100644 --- a/src/tests/io/test_open.f90 +++ b/src/tests/io/test_open.f90 @@ -80,6 +80,20 @@ program test_open u = open(filename, "r", io) call check(io /= 0) +! Sequential file +filename = get_outpath() // "/io_open.sequential" + +! Test mode "w" +u = open(filename, "wu") +write(u, *) 1, 2, 3 +close(u) + +! Test mode "r" +u = open(filename, "ru") +read(u, *) a +call check(all(a == [1, 2, 3])) +close(u) + contains diff --git a/src/tests/io/test_parse_mode.f90 b/src/tests/io/test_parse_mode.f90 index a94d96de4..b21752d33 100644 --- a/src/tests/io/test_parse_mode.f90 +++ b/src/tests/io/test_parse_mode.f90 @@ -183,5 +183,18 @@ subroutine test_parse_mode_always_fail() end subroutine + subroutine test_parse_mode_access() + character(1) :: m + + m = parse_mode("s") + call check(m == "r ts") + + m = parse_mode("u") + call check(m == "r tu") + + m = parse_mode("d") + call check(m == "r td") + + end subroutine test_parse_mode_access end program