Skip to content

Commit 7729b60

Browse files
committed
make interface: character or string_type
1 parent 6f87b42 commit 7729b60

File tree

2 files changed

+39
-14
lines changed

2 files changed

+39
-14
lines changed

doc/specs/stdlib_io.md

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -261,15 +261,16 @@ Provides formats for all kinds as defined in the `stdlib_kinds` module.
261261
{!example/io/example_fmt_constants.f90!}
262262
```
263263

264-
## `getfile` - Read a whole ASCII file into a string variable
264+
## `getfile` - Read a whole ASCII file into a `character` or a `string` variable
265265

266266
### Status
267267

268268
Experimental
269269

270270
### Description
271271

272-
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.
272+
This subroutine interface reads the entirety of a specified ASCII file and returns its content as a string or an allocatable `character` variable.
273+
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.
273274

274275
### Syntax
275276

@@ -282,7 +283,7 @@ Function
282283

283284
`filename`: Shall be a character input containing the path to the ASCII file to read. It is an `intent(in)` argument.
284285

285-
`file`: Shall be a `type(string_type)` variable containing the full content of the specified file. It is an `intent(out)` argument.
286+
`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.
286287

287288
`err` (optional): Shall be a `type(state_type)` variable. It is an `intent(out)` argument used for error handling.
288289

src/stdlib_io.fypp

Lines changed: 35 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ module stdlib_io
1616
implicit none
1717
private
1818
! Public API
19-
public :: loadtxt, savetxt, open, getline
19+
public :: loadtxt, savetxt, open, getline, getfile
2020

2121
!! version: experimental
2222
!!
@@ -35,7 +35,10 @@ module stdlib_io
3535
!!@note Handles errors using the library's `state_type` error-handling class. If not provided,
3636
!! exceptions will trigger an `error stop`.
3737
!!
38-
public :: getfile
38+
interface getfile
39+
module procedure :: getfile_char
40+
module procedure :: getfile_string
41+
end interface getfile
3942

4043
! Private API that is exposed so that we can test it in tests
4144
public :: parse_mode
@@ -551,7 +554,7 @@ contains
551554
!>
552555
!> Reads a whole ASCII file and loads its contents into a string variable.
553556
!> The function handles error states and optionally deletes the file after reading.
554-
subroutine getfile(fileName,file,err,delete)
557+
subroutine getfile_string(fileName,file,err,delete)
555558
!> Input file name
556559
character(*), intent(in) :: fileName
557560
!> Output string variable
@@ -562,16 +565,35 @@ contains
562565
logical, optional, intent(in) :: delete
563566

564567
! Local variables
565-
type(state_type) :: err0
566568
character(len=:), allocatable :: fileString
569+
570+
! Process output
571+
call getfile_char(fileName,fileString,err,delete)
572+
call move(from=fileString,to=file)
573+
574+
end subroutine getfile_string
575+
576+
!> Version: experimental
577+
!>
578+
!> Reads a whole ASCII file and loads its contents into an allocatable `character` variable.
579+
!> The function handles error states and optionally deletes the file after reading.
580+
subroutine getfile_char(fileName,file,err,delete)
581+
!> Input file name
582+
character(*), intent(in) :: fileName
583+
!> Output string variable
584+
character(len=:), allocatable, intent(out) :: file
585+
!> [optional] State return flag. On error, if not requested, the code will stop.
586+
type(state_type), optional, intent(out) :: err
587+
!> [optional] Delete file after reading? Default: do not delete
588+
logical, optional, intent(in) :: delete
589+
590+
! Local variables
591+
type(state_type) :: err0
567592
character(len=512) :: iomsg
568593
integer :: lun,iostat
569594
integer(int64) :: errpos,fileSize
570595
logical :: is_present,want_deleted
571596

572-
! Initializations
573-
file = ""
574-
575597
!> Check if the file should be deleted after reading
576598
if (present(delete)) then
577599
want_deleted = delete
@@ -582,6 +604,7 @@ contains
582604
!> Check file existing
583605
inquire(file=fileName, exist=is_present)
584606
if (.not.is_present) then
607+
allocate(character(len=0) :: file)
585608
err0 = state_type('getfile',STDLIB_IO_ERROR,'File not present:',fileName)
586609
call err0%handle(err)
587610
return
@@ -592,6 +615,7 @@ contains
592615

593616
invalid_size: if (fileSize<0) then
594617

618+
allocate(character(len=0) :: file)
595619
err0 = state_type('getfile',STDLIB_IO_ERROR,fileName,'has invalid size=',fileSize)
596620
call err0%handle(err)
597621
return
@@ -604,16 +628,17 @@ contains
604628
iostat=iostat,iomsg=iomsg)
605629

606630
if (iostat/=0) then
631+
allocate(character(len=0) :: file)
607632
err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot open',fileName,'for read:',iomsg)
608633
call err0%handle(err)
609634
return
610635
end if
611636

612-
allocate(character(len=fileSize) :: fileString)
637+
allocate(character(len=fileSize) :: file)
613638

614639
read_data: if (fileSize>0) then
615640

616-
read(lun, pos=1, iostat=iostat, iomsg=iomsg) fileString
641+
read(lun, pos=1, iostat=iostat, iomsg=iomsg) file
617642

618643
! Read error
619644
if (iostat/=0) then
@@ -636,9 +661,8 @@ contains
636661
endif
637662

638663
! Process output
639-
call move(from=fileString,to=file)
640664
call err0%handle(err)
641665

642-
end subroutine getfile
666+
end subroutine getfile_char
643667

644668
end module stdlib_io

0 commit comments

Comments
 (0)