From e98deaa17784bb43fb37d2f1f6ebbde139b11ec7 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Fri, 21 Feb 2025 12:00:22 +0100 Subject: [PATCH 01/25] add specs --- doc/specs/stdlib_io.md | 53 ++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 53 insertions(+) diff --git a/doc/specs/stdlib_io.md b/doc/specs/stdlib_io.md index 8c868802a..c38f1ac91 100644 --- a/doc/specs/stdlib_io.md +++ b/doc/specs/stdlib_io.md @@ -260,3 +260,56 @@ Provides formats for all kinds as defined in the `stdlib_kinds` module. ```fortran {!example/io/example_fmt_constants.f90!} ``` + +## `getfile` - Read a whole ASCII file into a string variable + +### Status + +Experimental + +### Description + +This function reads the entirety of a specified ASCII file and returns its content as a string. The function provides an optional error-handling mechanism via the `state_type` class. If the `err` argument is not provided, exceptions will trigger an `error stop`. The function also supports an optional flag to delete the file after reading. + +### Syntax + +`call [[stdlib_io(module):getfile(function)]] (fileName [, err] [, delete=.false.])` + +### Class +Function + +### Arguments + +`fileName`: Shall be a character input containing the path to the ASCII file to read. It is an `intent(in)` argument. + +`err` (optional): Shall be a `type(state_type)` variable. It is an `intent(out)` argument used for error handling. + +`delete` (optional): Shall be a `logical` flag. If `.true.`, the file is deleted after reading. Default is `.false.`. It is an `intent(in)` argument. + +### Return values + +The function returns a `string_type` variable containing the full content of the specified file. + +Raises `STDLIB_IO_ERROR` if the file is not found, cannot be opened, read, or deleted. +Exceptions trigger an `error stop` unless the optional `err` argument is provided. + +### Example + +```fortran +program example_getfile + use stdlib_io + implicit none + + type(string_type) :: fileContent + type(state_type) :: err + + ! Read a file into a string + fileContent = getfile("example.txt", err=err) + + if (err%error()) then + print *, "Error reading file:", err%print() + else + print *, "File content:", fileContent + end if +end program example_getfile +``` From 6d8a390a3efe3ce11ba1cdde768ba14f60248521 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Fri, 21 Feb 2025 12:01:56 +0100 Subject: [PATCH 02/25] add `getfile` --- src/stdlib_io.fypp | 113 ++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 112 insertions(+), 1 deletion(-) diff --git a/src/stdlib_io.fypp b/src/stdlib_io.fypp index 01b50a881..f7c8cf2de 100644 --- a/src/stdlib_io.fypp +++ b/src/stdlib_io.fypp @@ -9,7 +9,7 @@ module stdlib_io use, intrinsic :: iso_fortran_env, only : input_unit use stdlib_kinds, only: sp, dp, xdp, qp, & int8, int16, int32, int64 - use stdlib_error, only: error_stop + use stdlib_error, only: error_stop, state_type, STDLIB_IO_ERROR use stdlib_optval, only: optval use stdlib_ascii, only: is_blank use stdlib_string_type, only : string_type @@ -18,6 +18,25 @@ module stdlib_io ! Public API public :: loadtxt, savetxt, open, getline + !! version: experimental + !! + !! Reads a whole ASCII file and loads its contents into a string variable. + !! ([Specification](../page/specs/stdlib_io.html#getfile-read-a-whole-ascii-file-into-a-string-variable)) + !! + !!### Summary + !! Function interface for reading the content of a file into a string. + !! + !!### Description + !! + !! This function reads the entirety of a specified ASCII file and returns it as a string. The optional + !! `err` argument allows for handling errors through the library's `state_type` class. + !! An optional `logical` flag can be passed to delete the file after reading. + !! + !!@note Handles errors using the library's `state_type` error-handling class. If not provided, + !! exceptions will trigger an `error stop`. + !! + public :: getfile + ! Private API that is exposed so that we can test it in tests public :: parse_mode @@ -528,4 +547,96 @@ contains call getline(input_unit, line, iostat, iomsg) end subroutine getline_input_string + !> Version: experimental + !> + !> Reads a whole ASCII file and loads its contents into a string variable. + !> The function handles error states and optionally deletes the file after reading. + type(string_type) function getfile(fileName,err,delete) result(file) + !> Input file name + character(*), intent(in) :: fileName + !> [optional] State return flag. On error, if not requested, the code will stop. + type(state_type), optional, intent(out) :: err + !> [optional] Delete file after reading? Default: do not delete + logical, optional, intent(in) :: delete + + ! Local variables + type(state_type) :: err0 + character(len=:), allocatable :: fileString + character(len=512) :: iomsg + integer :: lun,iostat + integer(int64) :: errpos,fileSize + logical :: is_present,want_deleted + + ! Initializations + file = "" + + !> Check if the file should be deleted after reading + if (present(delete)) then + want_deleted = delete + else + want_deleted = .false. + end if + + !> Check file existing + inquire(file=fileName, exist=is_present) + if (.not.is_present) then + err0 = state_type('getfile',STDLIB_IO_ERROR,'File not present:',fileName) + call err0%handle(err) + return + end if + + !> Retrieve file size + inquire(file=fileName,size=fileSize) + + invalid_size: if (fileSize<0) then + + err0 = state_type('getfile',STDLIB_IO_ERROR,fileName,'has invalid size=',fileSize) + call err0%handle(err) + return + + endif invalid_size + + ! Read file + open(newunit=lun,file=fileName, & + form='unformatted',action='read',access='stream',status='old', & + iostat=iostat,iomsg=iomsg) + + if (iostat/=0) then + err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot open',fileName,'for read:',iomsg) + call err0%handle(err) + return + end if + + allocate(character(len=fileSize) :: fileString) + + read_data: if (fileSize>0) then + + read(lun, pos=1, iostat=iostat, iomsg=iomsg) fileString + + ! Read error + if (iostat/=0) then + + inquire(unit=lun,pos=errpos) + err0 = state_type('getfile',STDLIB_IO_ERROR,iomsg,'(',fileName,'at byte',errpos,')') + call err0%handle(err) + return + + endif + + end if read_data + + if (want_deleted) then + close(lun,iostat=iostat,status='delete') + if (iostat/=0) err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot delete',fileName,'after reading') + else + close(lun,iostat=iostat) + if (iostat/=0) err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot close',fileName,'after reading') + endif + + ! Process output + call move(from=fileString,to=file) + call err0%handle(err) + + end function getfile + end module stdlib_io From 448947f752b8b538d1608172a9f1591917893a20 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Fri, 21 Feb 2025 12:03:13 +0100 Subject: [PATCH 03/25] test `getfile` --- test/io/test_getline.f90 | 81 ++++++++++++++++++++++++++++++++++++++-- 1 file changed, 78 insertions(+), 3 deletions(-) diff --git a/test/io/test_getline.f90 b/test/io/test_getline.f90 index e035a904f..df1053f0a 100644 --- a/test/io/test_getline.f90 +++ b/test/io/test_getline.f90 @@ -1,6 +1,7 @@ module test_getline - use stdlib_io, only : getline - use stdlib_string_type, only : string_type, len + use stdlib_io, only : getline, getfile + use stdlib_error, only: state_type + use stdlib_string_type, only : string_type, len, len_trim use testdrive, only : new_unittest, unittest_type, error_type, check implicit none private @@ -20,7 +21,10 @@ subroutine collect_getline(testsuite) new_unittest("pad-no", test_pad_no), & new_unittest("iostat-end", test_iostat_end), & new_unittest("closed-unit", test_closed_unit, should_fail=.true.), & - new_unittest("no-unit", test_no_unit, should_fail=.true.) & + new_unittest("no-unit", test_no_unit, should_fail=.true.), & + new_unittest("getfile-no", test_getfile_missing), & + new_unittest("getfile-empty", test_getfile_empty), & + new_unittest("getfile-non-empty", test_getfile_non_empty) & ] end subroutine collect_getline @@ -139,6 +143,77 @@ subroutine test_no_unit(error) call check(error, stat, msg) end subroutine test_no_unit + subroutine test_getfile_missing(error) + !> Test for a missing file. + type(error_type), allocatable, intent(out) :: error + + type(string_type) :: fileContents + type(state_type) :: err + + fileContents = getfile("nonexistent_file.txt", err) + + ! Check that an error was returned + call check(error, err%error(), "Error not returned on a missing file") + if (allocated(error)) return + + end subroutine test_getfile_missing + + subroutine test_getfile_empty(error) + !> Test for an empty file. + type(error_type), allocatable, intent(out) :: error + + integer :: ios + character(len=:), allocatable :: filename + type(string_type) :: fileContents + type(state_type) :: err + + ! Get a temporary file name + filename = "test_getfile_empty.txt" + + ! Create an empty file + open(newunit=ios, file=filename, action="write", form="formatted", access="sequential") + close(ios) + + ! Read and delete it + fileContents = getfile(filename, err, delete=.true.) + + call check(error, err%ok(), "Should not return error reading an empty file") + if (allocated(error)) return + + call check(error, len_trim(fileContents) == 0, "String from empty file should be empty") + if (allocated(error)) return + + end subroutine test_getfile_empty + + subroutine test_getfile_non_empty(error) + !> Test for a non-empty file. + type(error_type), allocatable, intent(out) :: error + + integer :: ios + character(len=:), allocatable :: filename + type(string_type) :: fileContents + type(state_type) :: err + + ! Get a temporary file name + filename = "test_getfile_size5.txt" + + ! Create a fixed-size file + open(newunit=ios, file=filename, action="write", form="unformatted", access="stream") + write(ios) "12345" + close(ios) + + ! Read and delete it + fileContents = getfile(filename, err, delete=.true.) + + call check(error, err%ok(), "Should not return error reading a non-empty file") + if (allocated(error)) return + + call check(error, len_trim(fileContents) == 5, "Wrong string size returned") + if (allocated(error)) return + + end subroutine test_getfile_non_empty + + end module test_getline From 5e5d210e389c9073f94ef86ca9c670e5cb61960e Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Fri, 21 Feb 2025 12:04:53 +0100 Subject: [PATCH 04/25] add interface --- src/stdlib_io.fypp | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/stdlib_io.fypp b/src/stdlib_io.fypp index f7c8cf2de..3c9956163 100644 --- a/src/stdlib_io.fypp +++ b/src/stdlib_io.fypp @@ -12,7 +12,7 @@ module stdlib_io use stdlib_error, only: error_stop, state_type, STDLIB_IO_ERROR use stdlib_optval, only: optval use stdlib_ascii, only: is_blank - use stdlib_string_type, only : string_type + use stdlib_string_type, only : string_type, assignment(=), move implicit none private ! Public API From 02a180fe3f2c8b3089ca9a8c6ba3405136e65ac0 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Fri, 21 Feb 2025 12:09:24 +0100 Subject: [PATCH 05/25] create example program --- doc/specs/stdlib_io.md | 17 +---------------- example/io/CMakeLists.txt | 1 + example/io/example_getfile.f90 | 20 ++++++++++++++++++++ 3 files changed, 22 insertions(+), 16 deletions(-) create mode 100644 example/io/example_getfile.f90 diff --git a/doc/specs/stdlib_io.md b/doc/specs/stdlib_io.md index c38f1ac91..fce40fd9e 100644 --- a/doc/specs/stdlib_io.md +++ b/doc/specs/stdlib_io.md @@ -296,20 +296,5 @@ Exceptions trigger an `error stop` unless the optional `err` argument is provide ### Example ```fortran -program example_getfile - use stdlib_io - implicit none - - type(string_type) :: fileContent - type(state_type) :: err - - ! Read a file into a string - fileContent = getfile("example.txt", err=err) - - if (err%error()) then - print *, "Error reading file:", err%print() - else - print *, "File content:", fileContent - end if -end program example_getfile +{!example/io/example_getfile.f90!} ``` diff --git a/example/io/CMakeLists.txt b/example/io/CMakeLists.txt index 2e606d2d1..1ee891c6e 100644 --- a/example/io/CMakeLists.txt +++ b/example/io/CMakeLists.txt @@ -1,5 +1,6 @@ ADD_EXAMPLE(fmt_constants) #ADD_EXAMPLE(getline) +ADD_EXAMPLE(getfile) ADD_EXAMPLE(loadnpy) ADD_EXAMPLE(loadtxt) ADD_EXAMPLE(open) diff --git a/example/io/example_getfile.f90 b/example/io/example_getfile.f90 new file mode 100644 index 000000000..a27a6361f --- /dev/null +++ b/example/io/example_getfile.f90 @@ -0,0 +1,20 @@ +! Demonstrate usage of `getfile` +program example_getfile + use stdlib_io, only: getfile + use stdlib_string_type, only: string_type + use stdlib_error, only: state_type + implicit none + + character(*), parameter :: fileName = "example.txt" + type(string_type) :: fileContent + type(state_type) :: err + + ! Read a file into a string + fileContent = getfile(fileName, err=err) + + if (err%error()) then + print *, err%print() + else + print *, "Success! File "//fileName//" imported." + end if +end program example_getfile From 9eb4c0edf6bdeb50741b2e116cf3f0ad27e57894 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Fri, 21 Feb 2025 18:16:40 +0100 Subject: [PATCH 06/25] Update doc/specs/stdlib_io.md Co-authored-by: Jeremie Vandenplas --- doc/specs/stdlib_io.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/specs/stdlib_io.md b/doc/specs/stdlib_io.md index fce40fd9e..5e0c33962 100644 --- a/doc/specs/stdlib_io.md +++ b/doc/specs/stdlib_io.md @@ -280,7 +280,7 @@ Function ### Arguments -`fileName`: Shall be a character input containing the path to the ASCII file to read. It is an `intent(in)` argument. +`filename`: Shall be a character input containing the path to the ASCII file to read. It is an `intent(in)` argument. `err` (optional): Shall be a `type(state_type)` variable. It is an `intent(out)` argument used for error handling. From cee4ec72677934b5af4aa44bc1bb7e47a040d0f0 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Fri, 21 Feb 2025 18:16:47 +0100 Subject: [PATCH 07/25] Update doc/specs/stdlib_io.md Co-authored-by: Jeremie Vandenplas --- doc/specs/stdlib_io.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/specs/stdlib_io.md b/doc/specs/stdlib_io.md index 5e0c33962..01d185b91 100644 --- a/doc/specs/stdlib_io.md +++ b/doc/specs/stdlib_io.md @@ -273,7 +273,7 @@ This function reads the entirety of a specified ASCII file and returns its conte ### Syntax -`call [[stdlib_io(module):getfile(function)]] (fileName [, err] [, delete=.false.])` +`call [[stdlib_io(module):getfile(function)]] (filename [, err] [, delete=.false.])` ### Class Function From 56bedd52ff60cf6f10fd406a5173263a15eee71c Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Sat, 22 Feb 2025 09:24:22 +0100 Subject: [PATCH 08/25] function -> subroutine --- doc/specs/stdlib_io.md | 8 +++++--- example/io/example_getfile.f90 | 2 +- src/stdlib_io.fypp | 10 ++++++---- test/io/test_getline.f90 | 6 +++--- 4 files changed, 15 insertions(+), 11 deletions(-) diff --git a/doc/specs/stdlib_io.md b/doc/specs/stdlib_io.md index fce40fd9e..c3a20cfab 100644 --- a/doc/specs/stdlib_io.md +++ b/doc/specs/stdlib_io.md @@ -269,11 +269,11 @@ Experimental ### Description -This function reads the entirety of a specified ASCII file and returns its content as a string. The function provides an optional error-handling mechanism via the `state_type` class. If the `err` argument is not provided, exceptions will trigger an `error stop`. The function also supports an optional flag to delete the file after reading. +This subroutine reads the entirety of a specified ASCII file and returns its content as a string. The function provides an optional error-handling mechanism via the `state_type` class. If the `err` argument is not provided, exceptions will trigger an `error stop`. The function also supports an optional flag to delete the file after reading. ### Syntax -`call [[stdlib_io(module):getfile(function)]] (fileName [, err] [, delete=.false.])` +`call [[stdlib_io(module):getfile(function)]] (fileName, fileContents [, err] [, delete=.false.])` ### Class Function @@ -282,13 +282,15 @@ Function `fileName`: Shall be a character input containing the path to the ASCII file to read. It is an `intent(in)` argument. +`fileContents`: Shall be a `type(string_type)` variable containing the full content of the specified file. It is an `intent(out)` argument. + `err` (optional): Shall be a `type(state_type)` variable. It is an `intent(out)` argument used for error handling. `delete` (optional): Shall be a `logical` flag. If `.true.`, the file is deleted after reading. Default is `.false.`. It is an `intent(in)` argument. ### Return values -The function returns a `string_type` variable containing the full content of the specified file. +Output variable `fileContents` will contain the full content of the specified file. Raises `STDLIB_IO_ERROR` if the file is not found, cannot be opened, read, or deleted. Exceptions trigger an `error stop` unless the optional `err` argument is provided. diff --git a/example/io/example_getfile.f90 b/example/io/example_getfile.f90 index a27a6361f..8f8bf28d8 100644 --- a/example/io/example_getfile.f90 +++ b/example/io/example_getfile.f90 @@ -10,7 +10,7 @@ program example_getfile type(state_type) :: err ! Read a file into a string - fileContent = getfile(fileName, err=err) + call getfile(fileName, fileContent, err=err) if (err%error()) then print *, err%print() diff --git a/src/stdlib_io.fypp b/src/stdlib_io.fypp index 3c9956163..b2c4c53a3 100644 --- a/src/stdlib_io.fypp +++ b/src/stdlib_io.fypp @@ -24,11 +24,11 @@ module stdlib_io !! ([Specification](../page/specs/stdlib_io.html#getfile-read-a-whole-ascii-file-into-a-string-variable)) !! !!### Summary - !! Function interface for reading the content of a file into a string. + !! Subroutine interface for reading the content of a file into a string. !! !!### Description !! - !! This function reads the entirety of a specified ASCII file and returns it as a string. The optional + !! This subroutine reads the entirety of a specified ASCII file and returns it as a string. The optional !! `err` argument allows for handling errors through the library's `state_type` class. !! An optional `logical` flag can be passed to delete the file after reading. !! @@ -551,9 +551,11 @@ contains !> !> Reads a whole ASCII file and loads its contents into a string variable. !> The function handles error states and optionally deletes the file after reading. - type(string_type) function getfile(fileName,err,delete) result(file) + subroutine getfile(fileName,file,err,delete) !> Input file name character(*), intent(in) :: fileName + !> Output string variable + type(string_type), intent(out) :: file !> [optional] State return flag. On error, if not requested, the code will stop. type(state_type), optional, intent(out) :: err !> [optional] Delete file after reading? Default: do not delete @@ -637,6 +639,6 @@ contains call move(from=fileString,to=file) call err0%handle(err) - end function getfile + end subroutine getfile end module stdlib_io diff --git a/test/io/test_getline.f90 b/test/io/test_getline.f90 index df1053f0a..899446c83 100644 --- a/test/io/test_getline.f90 +++ b/test/io/test_getline.f90 @@ -150,7 +150,7 @@ subroutine test_getfile_missing(error) type(string_type) :: fileContents type(state_type) :: err - fileContents = getfile("nonexistent_file.txt", err) + call getfile("nonexistent_file.txt", fileContents, err) ! Check that an error was returned call check(error, err%error(), "Error not returned on a missing file") @@ -175,7 +175,7 @@ subroutine test_getfile_empty(error) close(ios) ! Read and delete it - fileContents = getfile(filename, err, delete=.true.) + call getfile(filename, fileContents, err, delete=.true.) call check(error, err%ok(), "Should not return error reading an empty file") if (allocated(error)) return @@ -203,7 +203,7 @@ subroutine test_getfile_non_empty(error) close(ios) ! Read and delete it - fileContents = getfile(filename, err, delete=.true.) + call getfile(filename, fileContents, err, delete=.true.) call check(error, err%ok(), "Should not return error reading a non-empty file") if (allocated(error)) return From 6f87b429b834a66d9063423eb92d6dba46731314 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Sat, 22 Feb 2025 09:25:43 +0100 Subject: [PATCH 09/25] Update stdlib_io.md --- doc/specs/stdlib_io.md | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/doc/specs/stdlib_io.md b/doc/specs/stdlib_io.md index fc7da461b..f853a8176 100644 --- a/doc/specs/stdlib_io.md +++ b/doc/specs/stdlib_io.md @@ -273,7 +273,7 @@ This subroutine reads the entirety of a specified ASCII file and returns its con ### Syntax -`call [[stdlib_io(module):getfile(function)]] (fileName, fileContents [, err] [, delete=.false.])` +`call [[stdlib_io(module):getfile(subroutine)]] (filename, file [, err] [, delete=.false.])` ### Class Function @@ -282,7 +282,7 @@ Function `filename`: Shall be a character input containing the path to the ASCII file to read. It is an `intent(in)` argument. -`fileContents`: Shall be a `type(string_type)` variable containing the full content of the specified file. It is an `intent(out)` argument. +`file`: Shall be a `type(string_type)` variable containing the full content of the specified file. It is an `intent(out)` argument. `err` (optional): Shall be a `type(state_type)` variable. It is an `intent(out)` argument used for error handling. @@ -290,7 +290,7 @@ Function ### Return values -Output variable `fileContents` will contain the full content of the specified file. +Output variable `file` will contain the full content of the specified file. Raises `STDLIB_IO_ERROR` if the file is not found, cannot be opened, read, or deleted. Exceptions trigger an `error stop` unless the optional `err` argument is provided. From 7729b601219f3d964ad4f8abf9b33a503417e62a Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Sat, 22 Feb 2025 09:30:34 +0100 Subject: [PATCH 10/25] make interface: `character` or `string_type` --- doc/specs/stdlib_io.md | 7 ++++--- src/stdlib_io.fypp | 46 ++++++++++++++++++++++++++++++++---------- 2 files changed, 39 insertions(+), 14 deletions(-) diff --git a/doc/specs/stdlib_io.md b/doc/specs/stdlib_io.md index f853a8176..2853ce24f 100644 --- a/doc/specs/stdlib_io.md +++ b/doc/specs/stdlib_io.md @@ -261,7 +261,7 @@ Provides formats for all kinds as defined in the `stdlib_kinds` module. {!example/io/example_fmt_constants.f90!} ``` -## `getfile` - Read a whole ASCII file into a string variable +## `getfile` - Read a whole ASCII file into a `character` or a `string` variable ### Status @@ -269,7 +269,8 @@ Experimental ### Description -This subroutine reads the entirety of a specified ASCII file and returns its content as a string. The function provides an optional error-handling mechanism via the `state_type` class. If the `err` argument is not provided, exceptions will trigger an `error stop`. The function also supports an optional flag to delete the file after reading. +This subroutine interface reads the entirety of a specified ASCII file and returns its content as a string or an allocatable `character` variable. +The function provides an optional error-handling mechanism via the `state_type` class. If the `err` argument is not provided, exceptions will trigger an `error stop`. The function also supports an optional flag to delete the file after reading. ### Syntax @@ -282,7 +283,7 @@ Function `filename`: Shall be a character input containing the path to the ASCII file to read. It is an `intent(in)` argument. -`file`: Shall be a `type(string_type)` variable containing the full content of the specified file. It is an `intent(out)` argument. +`file`: Shall be a `type(string_type)` or an allocatable `character` variable containing the full content of the specified file. It is an `intent(out)` argument. `err` (optional): Shall be a `type(state_type)` variable. It is an `intent(out)` argument used for error handling. diff --git a/src/stdlib_io.fypp b/src/stdlib_io.fypp index b2c4c53a3..9e4fb01ac 100644 --- a/src/stdlib_io.fypp +++ b/src/stdlib_io.fypp @@ -16,7 +16,7 @@ module stdlib_io implicit none private ! Public API - public :: loadtxt, savetxt, open, getline + public :: loadtxt, savetxt, open, getline, getfile !! version: experimental !! @@ -35,7 +35,10 @@ module stdlib_io !!@note Handles errors using the library's `state_type` error-handling class. If not provided, !! exceptions will trigger an `error stop`. !! - public :: getfile + interface getfile + module procedure :: getfile_char + module procedure :: getfile_string + end interface getfile ! Private API that is exposed so that we can test it in tests public :: parse_mode @@ -551,7 +554,7 @@ contains !> !> Reads a whole ASCII file and loads its contents into a string variable. !> The function handles error states and optionally deletes the file after reading. - subroutine getfile(fileName,file,err,delete) + subroutine getfile_string(fileName,file,err,delete) !> Input file name character(*), intent(in) :: fileName !> Output string variable @@ -562,16 +565,35 @@ contains logical, optional, intent(in) :: delete ! Local variables - type(state_type) :: err0 character(len=:), allocatable :: fileString + + ! Process output + call getfile_char(fileName,fileString,err,delete) + call move(from=fileString,to=file) + + end subroutine getfile_string + + !> Version: experimental + !> + !> Reads a whole ASCII file and loads its contents into an allocatable `character` variable. + !> The function handles error states and optionally deletes the file after reading. + subroutine getfile_char(fileName,file,err,delete) + !> Input file name + character(*), intent(in) :: fileName + !> Output string variable + character(len=:), allocatable, intent(out) :: file + !> [optional] State return flag. On error, if not requested, the code will stop. + type(state_type), optional, intent(out) :: err + !> [optional] Delete file after reading? Default: do not delete + logical, optional, intent(in) :: delete + + ! Local variables + type(state_type) :: err0 character(len=512) :: iomsg integer :: lun,iostat integer(int64) :: errpos,fileSize logical :: is_present,want_deleted - ! Initializations - file = "" - !> Check if the file should be deleted after reading if (present(delete)) then want_deleted = delete @@ -582,6 +604,7 @@ contains !> Check file existing inquire(file=fileName, exist=is_present) if (.not.is_present) then + allocate(character(len=0) :: file) err0 = state_type('getfile',STDLIB_IO_ERROR,'File not present:',fileName) call err0%handle(err) return @@ -592,6 +615,7 @@ contains invalid_size: if (fileSize<0) then + allocate(character(len=0) :: file) err0 = state_type('getfile',STDLIB_IO_ERROR,fileName,'has invalid size=',fileSize) call err0%handle(err) return @@ -604,16 +628,17 @@ contains iostat=iostat,iomsg=iomsg) if (iostat/=0) then + allocate(character(len=0) :: file) err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot open',fileName,'for read:',iomsg) call err0%handle(err) return end if - allocate(character(len=fileSize) :: fileString) + allocate(character(len=fileSize) :: file) read_data: if (fileSize>0) then - read(lun, pos=1, iostat=iostat, iomsg=iomsg) fileString + read(lun, pos=1, iostat=iostat, iomsg=iomsg) file ! Read error if (iostat/=0) then @@ -636,9 +661,8 @@ contains endif ! Process output - call move(from=fileString,to=file) call err0%handle(err) - end subroutine getfile + end subroutine getfile_char end module stdlib_io From 9a3ecda81b18316fa5b378cd4721cd21dd91a4f3 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Sat, 22 Feb 2025 09:32:10 +0100 Subject: [PATCH 11/25] fix link --- src/stdlib_io.fypp | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/stdlib_io.fypp b/src/stdlib_io.fypp index 9e4fb01ac..ad0e8f643 100644 --- a/src/stdlib_io.fypp +++ b/src/stdlib_io.fypp @@ -21,7 +21,7 @@ module stdlib_io !! version: experimental !! !! Reads a whole ASCII file and loads its contents into a string variable. - !! ([Specification](../page/specs/stdlib_io.html#getfile-read-a-whole-ascii-file-into-a-string-variable)) + !! ([Specification](../page/specs/stdlib_io.html#getfile-read-a-whole-ascii-file-into-a-character-or-a-string-variable)) !! !!### Summary !! Subroutine interface for reading the content of a file into a string. From a21c24b562401989b78bf4ff4707640197c87f75 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Tue, 25 Feb 2025 08:13:01 +0100 Subject: [PATCH 12/25] Update example/io/example_getfile.f90 Co-authored-by: jalvesz <102541118+jalvesz@users.noreply.github.com> --- example/io/example_getfile.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/example/io/example_getfile.f90 b/example/io/example_getfile.f90 index 8f8bf28d8..7ee7608a1 100644 --- a/example/io/example_getfile.f90 +++ b/example/io/example_getfile.f90 @@ -5,7 +5,7 @@ program example_getfile use stdlib_error, only: state_type implicit none - character(*), parameter :: fileName = "example.txt" + character(*), parameter :: filename = "example.txt" type(string_type) :: fileContent type(state_type) :: err From 1c6c0447fcc817f2b0468b36e96366df10ee1721 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Tue, 25 Feb 2025 08:13:13 +0100 Subject: [PATCH 13/25] Update example/io/example_getfile.f90 Co-authored-by: jalvesz <102541118+jalvesz@users.noreply.github.com> --- example/io/example_getfile.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/example/io/example_getfile.f90 b/example/io/example_getfile.f90 index 7ee7608a1..558baf80c 100644 --- a/example/io/example_getfile.f90 +++ b/example/io/example_getfile.f90 @@ -6,7 +6,7 @@ program example_getfile implicit none character(*), parameter :: filename = "example.txt" - type(string_type) :: fileContent + type(string_type) :: filecontent type(state_type) :: err ! Read a file into a string From 91c89bd6b2b8ee0f466edd3736e627703a78e0ee Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Tue, 25 Feb 2025 08:13:25 +0100 Subject: [PATCH 14/25] Update example/io/example_getfile.f90 Co-authored-by: jalvesz <102541118+jalvesz@users.noreply.github.com> --- example/io/example_getfile.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/example/io/example_getfile.f90 b/example/io/example_getfile.f90 index 558baf80c..6b1dd2653 100644 --- a/example/io/example_getfile.f90 +++ b/example/io/example_getfile.f90 @@ -10,7 +10,7 @@ program example_getfile type(state_type) :: err ! Read a file into a string - call getfile(fileName, fileContent, err=err) + call getfile(filename, filecontent, err=err) if (err%error()) then print *, err%print() From 16190ee5c2514a9b6e72f387917209cc1c6b5eab Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Tue, 25 Feb 2025 08:13:37 +0100 Subject: [PATCH 15/25] Update example/io/example_getfile.f90 Co-authored-by: jalvesz <102541118+jalvesz@users.noreply.github.com> --- example/io/example_getfile.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/example/io/example_getfile.f90 b/example/io/example_getfile.f90 index 6b1dd2653..88bd5757f 100644 --- a/example/io/example_getfile.f90 +++ b/example/io/example_getfile.f90 @@ -15,6 +15,6 @@ program example_getfile if (err%error()) then print *, err%print() else - print *, "Success! File "//fileName//" imported." + print *, "Success! File "//filename//" imported." end if end program example_getfile From 05fd08e90823869216a86872bee629938e85a8fb Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Tue, 25 Feb 2025 08:13:50 +0100 Subject: [PATCH 16/25] Update test/io/test_getline.f90 Co-authored-by: jalvesz <102541118+jalvesz@users.noreply.github.com> --- test/io/test_getline.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/io/test_getline.f90 b/test/io/test_getline.f90 index 899446c83..2522aba81 100644 --- a/test/io/test_getline.f90 +++ b/test/io/test_getline.f90 @@ -147,7 +147,7 @@ subroutine test_getfile_missing(error) !> Test for a missing file. type(error_type), allocatable, intent(out) :: error - type(string_type) :: fileContents + type(string_type) :: filecontents type(state_type) :: err call getfile("nonexistent_file.txt", fileContents, err) From 0c5a89566e1e909a30c6db0f4dbffd5e043d6659 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Tue, 25 Feb 2025 08:14:23 +0100 Subject: [PATCH 17/25] Update test/io/test_getline.f90 Co-authored-by: jalvesz <102541118+jalvesz@users.noreply.github.com> --- test/io/test_getline.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/io/test_getline.f90 b/test/io/test_getline.f90 index 2522aba81..8c4ef009f 100644 --- a/test/io/test_getline.f90 +++ b/test/io/test_getline.f90 @@ -203,7 +203,7 @@ subroutine test_getfile_non_empty(error) close(ios) ! Read and delete it - call getfile(filename, fileContents, err, delete=.true.) + call getfile(filename, filecontents, err, delete=.true.) call check(error, err%ok(), "Should not return error reading a non-empty file") if (allocated(error)) return From 8755ec634ad134b2c6b8dcb9c54ff7924153698e Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Tue, 25 Feb 2025 08:14:35 +0100 Subject: [PATCH 18/25] Update test/io/test_getline.f90 Co-authored-by: jalvesz <102541118+jalvesz@users.noreply.github.com> --- test/io/test_getline.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/io/test_getline.f90 b/test/io/test_getline.f90 index 8c4ef009f..9c790b552 100644 --- a/test/io/test_getline.f90 +++ b/test/io/test_getline.f90 @@ -191,7 +191,7 @@ subroutine test_getfile_non_empty(error) integer :: ios character(len=:), allocatable :: filename - type(string_type) :: fileContents + type(string_type) :: filecontents type(state_type) :: err ! Get a temporary file name From 9eb8fadcdd36cce2b0070786a803015d14fc4259 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Tue, 25 Feb 2025 08:14:47 +0100 Subject: [PATCH 19/25] Update test/io/test_getline.f90 Co-authored-by: jalvesz <102541118+jalvesz@users.noreply.github.com> --- test/io/test_getline.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/io/test_getline.f90 b/test/io/test_getline.f90 index 9c790b552..eec0db651 100644 --- a/test/io/test_getline.f90 +++ b/test/io/test_getline.f90 @@ -208,7 +208,7 @@ subroutine test_getfile_non_empty(error) call check(error, err%ok(), "Should not return error reading a non-empty file") if (allocated(error)) return - call check(error, len_trim(fileContents) == 5, "Wrong string size returned") + call check(error, len_trim(filecontents) == 5, "Wrong string size returned") if (allocated(error)) return end subroutine test_getfile_non_empty From 11e94738d20f02fa176852cf7c76dd34f09df76e Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Tue, 25 Feb 2025 08:15:02 +0100 Subject: [PATCH 20/25] Update src/stdlib_io.fypp Co-authored-by: jalvesz <102541118+jalvesz@users.noreply.github.com> --- src/stdlib_io.fypp | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/stdlib_io.fypp b/src/stdlib_io.fypp index ad0e8f643..c8f24fc2e 100644 --- a/src/stdlib_io.fypp +++ b/src/stdlib_io.fypp @@ -554,9 +554,9 @@ contains !> !> Reads a whole ASCII file and loads its contents into a string variable. !> The function handles error states and optionally deletes the file after reading. - subroutine getfile_string(fileName,file,err,delete) + subroutine getfile_string(filename,file,err,delete) !> Input file name - character(*), intent(in) :: fileName + character(*), intent(in) :: filename !> Output string variable type(string_type), intent(out) :: file !> [optional] State return flag. On error, if not requested, the code will stop. @@ -565,10 +565,10 @@ contains logical, optional, intent(in) :: delete ! Local variables - character(len=:), allocatable :: fileString + character(len=:), allocatable :: filestring ! Process output - call getfile_char(fileName,fileString,err,delete) + call getfile_char(filename,filestring,err,delete) call move(from=fileString,to=file) end subroutine getfile_string From 5efa730ef68fde117ee28aaa6a15c1587b3dd21f Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Tue, 25 Feb 2025 08:15:30 +0100 Subject: [PATCH 21/25] Update test/io/test_getline.f90 Co-authored-by: jalvesz <102541118+jalvesz@users.noreply.github.com> --- test/io/test_getline.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/io/test_getline.f90 b/test/io/test_getline.f90 index eec0db651..de366e889 100644 --- a/test/io/test_getline.f90 +++ b/test/io/test_getline.f90 @@ -164,7 +164,7 @@ subroutine test_getfile_empty(error) integer :: ios character(len=:), allocatable :: filename - type(string_type) :: fileContents + type(string_type) :: filecontents type(state_type) :: err ! Get a temporary file name From a5eef476cde469b689331a2f42a4e58a464ab751 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Tue, 25 Feb 2025 08:15:45 +0100 Subject: [PATCH 22/25] Update test/io/test_getline.f90 Co-authored-by: jalvesz <102541118+jalvesz@users.noreply.github.com> --- test/io/test_getline.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/io/test_getline.f90 b/test/io/test_getline.f90 index de366e889..c5a00c4ce 100644 --- a/test/io/test_getline.f90 +++ b/test/io/test_getline.f90 @@ -175,7 +175,7 @@ subroutine test_getfile_empty(error) close(ios) ! Read and delete it - call getfile(filename, fileContents, err, delete=.true.) + call getfile(filename, filecontents, err, delete=.true.) call check(error, err%ok(), "Should not return error reading an empty file") if (allocated(error)) return From d269649190a285e815180a72fb20fa34ba6bbe8b Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Tue, 25 Feb 2025 08:16:01 +0100 Subject: [PATCH 23/25] Update test/io/test_getline.f90 Co-authored-by: jalvesz <102541118+jalvesz@users.noreply.github.com> --- test/io/test_getline.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/io/test_getline.f90 b/test/io/test_getline.f90 index c5a00c4ce..34914579b 100644 --- a/test/io/test_getline.f90 +++ b/test/io/test_getline.f90 @@ -180,7 +180,7 @@ subroutine test_getfile_empty(error) call check(error, err%ok(), "Should not return error reading an empty file") if (allocated(error)) return - call check(error, len_trim(fileContents) == 0, "String from empty file should be empty") + call check(error, len_trim(filecontents) == 0, "String from empty file should be empty") if (allocated(error)) return end subroutine test_getfile_empty From 462d908c125eebf614ae715b129ed80417b90c28 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Tue, 25 Feb 2025 08:17:23 +0100 Subject: [PATCH 24/25] no camel --- src/stdlib_io.fypp | 30 +++++++++++++++--------------- 1 file changed, 15 insertions(+), 15 deletions(-) diff --git a/src/stdlib_io.fypp b/src/stdlib_io.fypp index c8f24fc2e..7b06da126 100644 --- a/src/stdlib_io.fypp +++ b/src/stdlib_io.fypp @@ -577,9 +577,9 @@ contains !> !> Reads a whole ASCII file and loads its contents into an allocatable `character` variable. !> The function handles error states and optionally deletes the file after reading. - subroutine getfile_char(fileName,file,err,delete) + subroutine getfile_char(filename,file,err,delete) !> Input file name - character(*), intent(in) :: fileName + character(*), intent(in) :: filename !> Output string variable character(len=:), allocatable, intent(out) :: file !> [optional] State return flag. On error, if not requested, the code will stop. @@ -591,7 +591,7 @@ contains type(state_type) :: err0 character(len=512) :: iomsg integer :: lun,iostat - integer(int64) :: errpos,fileSize + integer(int64) :: errpos,file_size logical :: is_present,want_deleted !> Check if the file should be deleted after reading @@ -602,41 +602,41 @@ contains end if !> Check file existing - inquire(file=fileName, exist=is_present) + inquire(file=filename, exist=is_present) if (.not.is_present) then allocate(character(len=0) :: file) - err0 = state_type('getfile',STDLIB_IO_ERROR,'File not present:',fileName) + err0 = state_type('getfile',STDLIB_IO_ERROR,'File not present:',filename) call err0%handle(err) return end if !> Retrieve file size - inquire(file=fileName,size=fileSize) + inquire(file=filename,size=file_size) - invalid_size: if (fileSize<0) then + invalid_size: if (file_size<0) then allocate(character(len=0) :: file) - err0 = state_type('getfile',STDLIB_IO_ERROR,fileName,'has invalid size=',fileSize) + err0 = state_type('getfile',STDLIB_IO_ERROR,filename,'has invalid size=',file_size) call err0%handle(err) return endif invalid_size ! Read file - open(newunit=lun,file=fileName, & + open(newunit=lun,file=filename, & form='unformatted',action='read',access='stream',status='old', & iostat=iostat,iomsg=iomsg) if (iostat/=0) then allocate(character(len=0) :: file) - err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot open',fileName,'for read:',iomsg) + err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot open',filename,'for read:',iomsg) call err0%handle(err) return end if - allocate(character(len=fileSize) :: file) + allocate(character(len=file_size) :: file) - read_data: if (fileSize>0) then + read_data: if (file_size>0) then read(lun, pos=1, iostat=iostat, iomsg=iomsg) file @@ -644,7 +644,7 @@ contains if (iostat/=0) then inquire(unit=lun,pos=errpos) - err0 = state_type('getfile',STDLIB_IO_ERROR,iomsg,'(',fileName,'at byte',errpos,')') + err0 = state_type('getfile',STDLIB_IO_ERROR,iomsg,'(',filename,'at byte',errpos,')') call err0%handle(err) return @@ -654,10 +654,10 @@ contains if (want_deleted) then close(lun,iostat=iostat,status='delete') - if (iostat/=0) err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot delete',fileName,'after reading') + if (iostat/=0) err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot delete',filename,'after reading') else close(lun,iostat=iostat) - if (iostat/=0) err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot close',fileName,'after reading') + if (iostat/=0) err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot close',filename,'after reading') endif ! Process output From 36031fc549bd25f9f805234703ef0c439125ae52 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Wed, 26 Feb 2025 16:09:36 +0100 Subject: [PATCH 25/25] underscore --- doc/specs/stdlib_io.md | 14 ++-- example/io/CMakeLists.txt | 4 +- ...ample_getfile.f90 => example_get_file.f90} | 10 +-- ...ample_getline.f90 => example_get_line.f90} | 6 +- src/stdlib_io.fypp | 70 +++++++++---------- test/io/CMakeLists.txt | 2 +- .../{test_getline.f90 => test_get_line.f90} | 58 +++++++-------- 7 files changed, 82 insertions(+), 82 deletions(-) rename example/io/{example_getfile.f90 => example_get_file.f90} (68%) rename example/io/{example_getline.f90 => example_get_line.f90} (69%) rename test/io/{test_getline.f90 => test_get_line.f90} (82%) diff --git a/doc/specs/stdlib_io.md b/doc/specs/stdlib_io.md index 2853ce24f..0ae2b11b3 100644 --- a/doc/specs/stdlib_io.md +++ b/doc/specs/stdlib_io.md @@ -205,7 +205,7 @@ Provides a npy file called `filename` that contains the rank-2 `array`. {!example/io/example_savenpy.f90!} ``` -## `getline` +## `get_line` ### Status @@ -217,9 +217,9 @@ Read a whole line from a formatted unit into a string variable ### Syntax -`call ` [[stdlib_io(module):getline(interface)]] ` (unit, line[, iostat][, iomsg])` +`call ` [[stdlib_io(module):get_line(interface)]] ` (unit, line[, iostat][, iomsg])` -`call ` [[stdlib_io(module):getline(interface)]] ` (line[, iostat][, iomsg])` +`call ` [[stdlib_io(module):get_line(interface)]] ` (line[, iostat][, iomsg])` ### Arguments @@ -241,7 +241,7 @@ Read a whole line from a formatted unit into a string variable ### Example ```fortran -{!example/io/example_getline.f90!} +{!example/io/example_get_line.f90!} ``` ## Formatting constants @@ -261,7 +261,7 @@ Provides formats for all kinds as defined in the `stdlib_kinds` module. {!example/io/example_fmt_constants.f90!} ``` -## `getfile` - Read a whole ASCII file into a `character` or a `string` variable +## `get_file` - Read a whole ASCII file into a `character` or a `string` variable ### Status @@ -274,7 +274,7 @@ The function provides an optional error-handling mechanism via the `state_type` ### Syntax -`call [[stdlib_io(module):getfile(subroutine)]] (filename, file [, err] [, delete=.false.])` +`call [[stdlib_io(module):get_file(subroutine)]] (filename, file [, err] [, delete=.false.])` ### Class Function @@ -299,5 +299,5 @@ Exceptions trigger an `error stop` unless the optional `err` argument is provide ### Example ```fortran -{!example/io/example_getfile.f90!} +{!example/io/example_get_file.f90!} ``` diff --git a/example/io/CMakeLists.txt b/example/io/CMakeLists.txt index 1ee891c6e..db663f537 100644 --- a/example/io/CMakeLists.txt +++ b/example/io/CMakeLists.txt @@ -1,6 +1,6 @@ ADD_EXAMPLE(fmt_constants) -#ADD_EXAMPLE(getline) -ADD_EXAMPLE(getfile) +#ADD_EXAMPLE(get_line) +ADD_EXAMPLE(get_file) ADD_EXAMPLE(loadnpy) ADD_EXAMPLE(loadtxt) ADD_EXAMPLE(open) diff --git a/example/io/example_getfile.f90 b/example/io/example_get_file.f90 similarity index 68% rename from example/io/example_getfile.f90 rename to example/io/example_get_file.f90 index 88bd5757f..bb0a2743a 100644 --- a/example/io/example_getfile.f90 +++ b/example/io/example_get_file.f90 @@ -1,6 +1,6 @@ -! Demonstrate usage of `getfile` -program example_getfile - use stdlib_io, only: getfile +! Demonstrate usage of `get_file` +program example_get_file + use stdlib_io, only: get_file use stdlib_string_type, only: string_type use stdlib_error, only: state_type implicit none @@ -10,11 +10,11 @@ program example_getfile type(state_type) :: err ! Read a file into a string - call getfile(filename, filecontent, err=err) + call get_file(filename, filecontent, err=err) if (err%error()) then print *, err%print() else print *, "Success! File "//filename//" imported." end if -end program example_getfile +end program example_get_file diff --git a/example/io/example_getline.f90 b/example/io/example_get_line.f90 similarity index 69% rename from example/io/example_getline.f90 rename to example/io/example_get_line.f90 index f61265099..a641f933c 100644 --- a/example/io/example_getline.f90 +++ b/example/io/example_get_line.f90 @@ -1,13 +1,13 @@ program example_getline use, intrinsic :: iso_fortran_env, only: input_unit, output_unit - use stdlib_io, only: getline + use stdlib_io, only: get_line implicit none character(len=:), allocatable :: line integer :: stat - call getline(input_unit, line, stat) + call get_line(input_unit, line, stat) do while (stat == 0) write (output_unit, '(a)') line - call getline(input_unit, line, stat) + call get_line(input_unit, line, stat) end do end program example_getline diff --git a/src/stdlib_io.fypp b/src/stdlib_io.fypp index 7b06da126..8e45d8c80 100644 --- a/src/stdlib_io.fypp +++ b/src/stdlib_io.fypp @@ -16,12 +16,12 @@ module stdlib_io implicit none private ! Public API - public :: loadtxt, savetxt, open, getline, getfile + public :: loadtxt, savetxt, open, get_line, get_file !! version: experimental !! !! Reads a whole ASCII file and loads its contents into a string variable. - !! ([Specification](../page/specs/stdlib_io.html#getfile-read-a-whole-ascii-file-into-a-character-or-a-string-variable)) + !! ([Specification](../page/specs/stdlib_io.html#get-file-read-a-whole-ascii-file-into-a-character-or-a-string-variable)) !! !!### Summary !! Subroutine interface for reading the content of a file into a string. @@ -35,10 +35,10 @@ module stdlib_io !!@note Handles errors using the library's `state_type` error-handling class. If not provided, !! exceptions will trigger an `error stop`. !! - interface getfile - module procedure :: getfile_char - module procedure :: getfile_string - end interface getfile + interface get_file + module procedure :: get_file_char + module procedure :: get_file_string + end interface get_file ! Private API that is exposed so that we can test it in tests public :: parse_mode @@ -73,12 +73,12 @@ module stdlib_io !> Version: experimental !> !> Read a whole line from a formatted unit into a string variable - interface getline - module procedure :: getline_char - module procedure :: getline_string - module procedure :: getline_input_char - module procedure :: getline_input_string - end interface getline + interface get_line + module procedure :: get_line_char + module procedure :: get_line_string + module procedure :: get_line_input_char + module procedure :: get_line_input_string + end interface get_line interface loadtxt !! version: experimental @@ -287,7 +287,7 @@ contains number_of_columns = 0 ! Read first non-skipped line as a whole - call getline(s, line, ios) + call get_line(s, line, ios) if (ios/=0 .or. .not.allocated(line)) return lastblank = .true. @@ -459,7 +459,7 @@ contains !> Version: experimental !> !> Read a whole line from a formatted unit into a deferred length character variable - subroutine getline_char(unit, line, iostat, iomsg) + subroutine get_line_char(unit, line, iostat, iomsg) !> Formatted IO unit integer, intent(in) :: unit !> Line to read @@ -501,12 +501,12 @@ contains else if (stat /= 0) then call error_stop(trim(msg)) end if - end subroutine getline_char + end subroutine get_line_char !> Version: experimental !> !> Read a whole line from a formatted unit into a string variable - subroutine getline_string(unit, line, iostat, iomsg) + subroutine get_line_string(unit, line, iostat, iomsg) !> Formatted IO unit integer, intent(in) :: unit !> Line to read @@ -518,14 +518,14 @@ contains character(len=:), allocatable :: buffer - call getline(unit, buffer, iostat, iomsg) + call get_line(unit, buffer, iostat, iomsg) line = string_type(buffer) - end subroutine getline_string + end subroutine get_line_string !> Version: experimental !> !> Read a whole line from the standard input into a deferred length character variable - subroutine getline_input_char(line, iostat, iomsg) + subroutine get_line_input_char(line, iostat, iomsg) !> Line to read character(len=:), allocatable, intent(out) :: line !> Status of operation @@ -533,13 +533,13 @@ contains !> Error message character(len=:), allocatable, optional :: iomsg - call getline(input_unit, line, iostat, iomsg) - end subroutine getline_input_char + call get_line(input_unit, line, iostat, iomsg) + end subroutine get_line_input_char !> Version: experimental !> !> Read a whole line from the standard input into a string variable - subroutine getline_input_string(line, iostat, iomsg) + subroutine get_line_input_string(line, iostat, iomsg) !> Line to read type(string_type), intent(out) :: line !> Status of operation @@ -547,14 +547,14 @@ contains !> Error message character(len=:), allocatable, optional :: iomsg - call getline(input_unit, line, iostat, iomsg) - end subroutine getline_input_string + call get_line(input_unit, line, iostat, iomsg) + end subroutine get_line_input_string !> Version: experimental !> !> Reads a whole ASCII file and loads its contents into a string variable. !> The function handles error states and optionally deletes the file after reading. - subroutine getfile_string(filename,file,err,delete) + subroutine get_file_string(filename,file,err,delete) !> Input file name character(*), intent(in) :: filename !> Output string variable @@ -568,16 +568,16 @@ contains character(len=:), allocatable :: filestring ! Process output - call getfile_char(filename,filestring,err,delete) + call get_file_char(filename,filestring,err,delete) call move(from=fileString,to=file) - end subroutine getfile_string + end subroutine get_file_string !> Version: experimental !> !> Reads a whole ASCII file and loads its contents into an allocatable `character` variable. !> The function handles error states and optionally deletes the file after reading. - subroutine getfile_char(filename,file,err,delete) + subroutine get_file_char(filename,file,err,delete) !> Input file name character(*), intent(in) :: filename !> Output string variable @@ -605,7 +605,7 @@ contains inquire(file=filename, exist=is_present) if (.not.is_present) then allocate(character(len=0) :: file) - err0 = state_type('getfile',STDLIB_IO_ERROR,'File not present:',filename) + err0 = state_type('get_file',STDLIB_IO_ERROR,'File not present:',filename) call err0%handle(err) return end if @@ -616,7 +616,7 @@ contains invalid_size: if (file_size<0) then allocate(character(len=0) :: file) - err0 = state_type('getfile',STDLIB_IO_ERROR,filename,'has invalid size=',file_size) + err0 = state_type('get_file',STDLIB_IO_ERROR,filename,'has invalid size=',file_size) call err0%handle(err) return @@ -629,7 +629,7 @@ contains if (iostat/=0) then allocate(character(len=0) :: file) - err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot open',filename,'for read:',iomsg) + err0 = state_type('get_file',STDLIB_IO_ERROR,'Cannot open',filename,'for read:',iomsg) call err0%handle(err) return end if @@ -644,7 +644,7 @@ contains if (iostat/=0) then inquire(unit=lun,pos=errpos) - err0 = state_type('getfile',STDLIB_IO_ERROR,iomsg,'(',filename,'at byte',errpos,')') + err0 = state_type('get_file',STDLIB_IO_ERROR,iomsg,'(',filename,'at byte',errpos,')') call err0%handle(err) return @@ -654,15 +654,15 @@ contains if (want_deleted) then close(lun,iostat=iostat,status='delete') - if (iostat/=0) err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot delete',filename,'after reading') + if (iostat/=0) err0 = state_type('get_file',STDLIB_IO_ERROR,'Cannot delete',filename,'after reading') else close(lun,iostat=iostat) - if (iostat/=0) err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot close',filename,'after reading') + if (iostat/=0) err0 = state_type('get_file',STDLIB_IO_ERROR,'Cannot close',filename,'after reading') endif ! Process output call err0%handle(err) - end subroutine getfile_char + end subroutine get_file_char end module stdlib_io diff --git a/test/io/CMakeLists.txt b/test/io/CMakeLists.txt index 98794cd88..4e19b5fbe 100644 --- a/test/io/CMakeLists.txt +++ b/test/io/CMakeLists.txt @@ -13,7 +13,7 @@ ADDTEST(savetxt_qp) set_tests_properties(loadtxt_qp PROPERTIES LABELS quadruple_precision) set_tests_properties(savetxt_qp PROPERTIES LABELS quadruple_precision) -ADDTEST(getline) +ADDTEST(get_line) ADDTEST(npy) ADDTEST(open) ADDTEST(parse_mode) diff --git a/test/io/test_getline.f90 b/test/io/test_get_line.f90 similarity index 82% rename from test/io/test_getline.f90 rename to test/io/test_get_line.f90 index 34914579b..d83bab06d 100644 --- a/test/io/test_getline.f90 +++ b/test/io/test_get_line.f90 @@ -1,17 +1,17 @@ -module test_getline - use stdlib_io, only : getline, getfile +module test_get_line + use stdlib_io, only : get_line, get_file use stdlib_error, only: state_type use stdlib_string_type, only : string_type, len, len_trim use testdrive, only : new_unittest, unittest_type, error_type, check implicit none private - public :: collect_getline + public :: collect_get_line contains !> Collect all exported unit tests - subroutine collect_getline(testsuite) + subroutine collect_get_line(testsuite) !> Collection of tests type(unittest_type), allocatable, intent(out) :: testsuite(:) @@ -22,11 +22,11 @@ subroutine collect_getline(testsuite) new_unittest("iostat-end", test_iostat_end), & new_unittest("closed-unit", test_closed_unit, should_fail=.true.), & new_unittest("no-unit", test_no_unit, should_fail=.true.), & - new_unittest("getfile-no", test_getfile_missing), & - new_unittest("getfile-empty", test_getfile_empty), & - new_unittest("getfile-non-empty", test_getfile_non_empty) & + new_unittest("get_file-no", test_get_file_missing), & + new_unittest("get_file-empty", test_get_file_empty), & + new_unittest("get_file-non-empty", test_get_file_non_empty) & ] - end subroutine collect_getline + end subroutine collect_get_line subroutine test_read_char(error) !> Error handling @@ -40,7 +40,7 @@ subroutine test_read_char(error) rewind(io) do i = 1, 3 - call getline(io, line, stat) + call get_line(io, line, stat) call check(error, stat) if (allocated(error)) exit call check(error, len(line), 3*10**i) @@ -61,7 +61,7 @@ subroutine test_read_string(error) rewind(io) do i = 1, 3 - call getline(io, line, stat) + call get_line(io, line, stat) call check(error, stat) if (allocated(error)) exit call check(error, len(line), 3*10**i) @@ -82,7 +82,7 @@ subroutine test_pad_no(error) rewind(io) do i = 1, 3 - call getline(io, line, stat) + call get_line(io, line, stat) call check(error, stat) if (allocated(error)) exit call check(error, len(line), 3*10**i) @@ -104,14 +104,14 @@ subroutine test_iostat_end(error) rewind(io) do i = 1, 3 - call getline(io, line, stat) + call get_line(io, line, stat) call check(error, stat) if (allocated(error)) exit call check(error, len(line), 3*10**i) if (allocated(error)) exit end do if (.not.allocated(error)) then - call getline(io, line, stat) + call get_line(io, line, stat) call check(error, stat, iostat_end) end if close(io) @@ -127,7 +127,7 @@ subroutine test_closed_unit(error) open(newunit=io, status="scratch") close(io) - call getline(io, line, stat, msg) + call get_line(io, line, stat, msg) call check(error, stat, msg) end subroutine test_closed_unit @@ -139,26 +139,26 @@ subroutine test_no_unit(error) character(len=:), allocatable :: line, msg io = -1 - call getline(io, line, stat, msg) + call get_line(io, line, stat, msg) call check(error, stat, msg) end subroutine test_no_unit - subroutine test_getfile_missing(error) + subroutine test_get_file_missing(error) !> Test for a missing file. type(error_type), allocatable, intent(out) :: error type(string_type) :: filecontents type(state_type) :: err - call getfile("nonexistent_file.txt", fileContents, err) + call get_file("nonexistent_file.txt", fileContents, err) ! Check that an error was returned call check(error, err%error(), "Error not returned on a missing file") if (allocated(error)) return - end subroutine test_getfile_missing + end subroutine test_get_file_missing - subroutine test_getfile_empty(error) + subroutine test_get_file_empty(error) !> Test for an empty file. type(error_type), allocatable, intent(out) :: error @@ -168,14 +168,14 @@ subroutine test_getfile_empty(error) type(state_type) :: err ! Get a temporary file name - filename = "test_getfile_empty.txt" + filename = "test_get_file_empty.txt" ! Create an empty file open(newunit=ios, file=filename, action="write", form="formatted", access="sequential") close(ios) ! Read and delete it - call getfile(filename, filecontents, err, delete=.true.) + call get_file(filename, filecontents, err, delete=.true.) call check(error, err%ok(), "Should not return error reading an empty file") if (allocated(error)) return @@ -183,9 +183,9 @@ subroutine test_getfile_empty(error) call check(error, len_trim(filecontents) == 0, "String from empty file should be empty") if (allocated(error)) return - end subroutine test_getfile_empty + end subroutine test_get_file_empty - subroutine test_getfile_non_empty(error) + subroutine test_get_file_non_empty(error) !> Test for a non-empty file. type(error_type), allocatable, intent(out) :: error @@ -195,7 +195,7 @@ subroutine test_getfile_non_empty(error) type(state_type) :: err ! Get a temporary file name - filename = "test_getfile_size5.txt" + filename = "test_get_file_size5.txt" ! Create a fixed-size file open(newunit=ios, file=filename, action="write", form="unformatted", access="stream") @@ -203,7 +203,7 @@ subroutine test_getfile_non_empty(error) close(ios) ! Read and delete it - call getfile(filename, filecontents, err, delete=.true.) + call get_file(filename, filecontents, err, delete=.true.) call check(error, err%ok(), "Should not return error reading a non-empty file") if (allocated(error)) return @@ -211,16 +211,16 @@ subroutine test_getfile_non_empty(error) call check(error, len_trim(filecontents) == 5, "Wrong string size returned") if (allocated(error)) return - end subroutine test_getfile_non_empty + end subroutine test_get_file_non_empty -end module test_getline +end module test_get_line program tester use, intrinsic :: iso_fortran_env, only : error_unit use testdrive, only : run_testsuite, new_testsuite, testsuite_type - use test_getline, only : collect_getline + use test_get_line, only : collect_get_line implicit none integer :: stat, is type(testsuite_type), allocatable :: testsuites(:) @@ -229,7 +229,7 @@ program tester stat = 0 testsuites = [ & - new_testsuite("getline", collect_getline) & + new_testsuite("get_line", collect_get_line) & ] do is = 1, size(testsuites)