@@ -9,14 +9,36 @@ module stdlib_io
99 use, intrinsic :: iso_fortran_env, only : input_unit
1010 use stdlib_kinds, only: sp, dp, xdp, qp, &
1111 int8, int16, int32, int64
12- use stdlib_error, only: error_stop
12+ use stdlib_error, only: error_stop, state_type, STDLIB_IO_ERROR
1313 use stdlib_optval, only: optval
1414 use stdlib_ascii, only: is_blank
15- use stdlib_string_type, only : string_type
15+ use stdlib_string_type, only : string_type, assignment(=), move
1616 implicit none
1717 private
1818 ! Public API
19- public :: loadtxt, savetxt, open, getline
19+ public :: loadtxt, savetxt, open, get_line, get_file
20+
21+ !! version: experimental
22+ !!
23+ !! Reads a whole ASCII file and loads its contents into a string variable.
24+ !! ([Specification](../page/specs/stdlib_io.html#get-file-read-a-whole-ascii-file-into-a-character-or-a-string-variable))
25+ !!
26+ !!### Summary
27+ !! Subroutine interface for reading the content of a file into a string.
28+ !!
29+ !!### Description
30+ !!
31+ !! This subroutine reads the entirety of a specified ASCII file and returns it as a string. The optional
32+ !! `err` argument allows for handling errors through the library's `state_type` class.
33+ !! An optional `logical` flag can be passed to delete the file after reading.
34+ !!
35+ !!@note Handles errors using the library's `state_type` error-handling class. If not provided,
36+ !! exceptions will trigger an `error stop`.
37+ !!
38+ interface get_file
39+ module procedure :: get_file_char
40+ module procedure :: get_file_string
41+ end interface get_file
2042
2143 ! Private API that is exposed so that we can test it in tests
2244 public :: parse_mode
@@ -51,12 +73,12 @@ module stdlib_io
5173 !> Version: experimental
5274 !>
5375 !> Read a whole line from a formatted unit into a string variable
54- interface getline
55- module procedure :: getline_char
56- module procedure :: getline_string
57- module procedure :: getline_input_char
58- module procedure :: getline_input_string
59- end interface getline
76+ interface get_line
77+ module procedure :: get_line_char
78+ module procedure :: get_line_string
79+ module procedure :: get_line_input_char
80+ module procedure :: get_line_input_string
81+ end interface get_line
6082
6183 interface loadtxt
6284 !! version: experimental
@@ -265,7 +287,7 @@ contains
265287 number_of_columns = 0
266288
267289 ! Read first non-skipped line as a whole
268- call getline (s, line, ios)
290+ call get_line (s, line, ios)
269291 if (ios/=0 .or. .not.allocated(line)) return
270292
271293 lastblank = .true.
@@ -437,7 +459,7 @@ contains
437459 !> Version: experimental
438460 !>
439461 !> Read a whole line from a formatted unit into a deferred length character variable
440- subroutine getline_char (unit, line, iostat, iomsg)
462+ subroutine get_line_char (unit, line, iostat, iomsg)
441463 !> Formatted IO unit
442464 integer, intent(in) :: unit
443465 !> Line to read
@@ -479,12 +501,12 @@ contains
479501 else if (stat /= 0) then
480502 call error_stop(trim(msg))
481503 end if
482- end subroutine getline_char
504+ end subroutine get_line_char
483505
484506 !> Version: experimental
485507 !>
486508 !> Read a whole line from a formatted unit into a string variable
487- subroutine getline_string (unit, line, iostat, iomsg)
509+ subroutine get_line_string (unit, line, iostat, iomsg)
488510 !> Formatted IO unit
489511 integer, intent(in) :: unit
490512 !> Line to read
@@ -496,36 +518,151 @@ contains
496518
497519 character(len=:), allocatable :: buffer
498520
499- call getline (unit, buffer, iostat, iomsg)
521+ call get_line (unit, buffer, iostat, iomsg)
500522 line = string_type(buffer)
501- end subroutine getline_string
523+ end subroutine get_line_string
502524
503525 !> Version: experimental
504526 !>
505527 !> Read a whole line from the standard input into a deferred length character variable
506- subroutine getline_input_char (line, iostat, iomsg)
528+ subroutine get_line_input_char (line, iostat, iomsg)
507529 !> Line to read
508530 character(len=:), allocatable, intent(out) :: line
509531 !> Status of operation
510532 integer, intent(out), optional :: iostat
511533 !> Error message
512534 character(len=:), allocatable, optional :: iomsg
513535
514- call getline (input_unit, line, iostat, iomsg)
515- end subroutine getline_input_char
536+ call get_line (input_unit, line, iostat, iomsg)
537+ end subroutine get_line_input_char
516538
517539 !> Version: experimental
518540 !>
519541 !> Read a whole line from the standard input into a string variable
520- subroutine getline_input_string (line, iostat, iomsg)
542+ subroutine get_line_input_string (line, iostat, iomsg)
521543 !> Line to read
522544 type(string_type), intent(out) :: line
523545 !> Status of operation
524546 integer, intent(out), optional :: iostat
525547 !> Error message
526548 character(len=:), allocatable, optional :: iomsg
527549
528- call getline(input_unit, line, iostat, iomsg)
529- end subroutine getline_input_string
550+ call get_line(input_unit, line, iostat, iomsg)
551+ end subroutine get_line_input_string
552+
553+ !> Version: experimental
554+ !>
555+ !> Reads a whole ASCII file and loads its contents into a string variable.
556+ !> The function handles error states and optionally deletes the file after reading.
557+ subroutine get_file_string(filename,file,err,delete)
558+ !> Input file name
559+ character(*), intent(in) :: filename
560+ !> Output string variable
561+ type(string_type), intent(out) :: file
562+ !> [optional] State return flag. On error, if not requested, the code will stop.
563+ type(state_type), optional, intent(out) :: err
564+ !> [optional] Delete file after reading? Default: do not delete
565+ logical, optional, intent(in) :: delete
566+
567+ ! Local variables
568+ character(len=:), allocatable :: filestring
569+
570+ ! Process output
571+ call get_file_char(filename,filestring,err,delete)
572+ call move(from=fileString,to=file)
573+
574+ end subroutine get_file_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 get_file_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
592+ character(len=512) :: iomsg
593+ integer :: lun,iostat
594+ integer(int64) :: errpos,file_size
595+ logical :: is_present,want_deleted
596+
597+ !> Check if the file should be deleted after reading
598+ if (present(delete)) then
599+ want_deleted = delete
600+ else
601+ want_deleted = .false.
602+ end if
603+
604+ !> Check file existing
605+ inquire(file=filename, exist=is_present)
606+ if (.not.is_present) then
607+ allocate(character(len=0) :: file)
608+ err0 = state_type('get_file',STDLIB_IO_ERROR,'File not present:',filename)
609+ call err0%handle(err)
610+ return
611+ end if
612+
613+ !> Retrieve file size
614+ inquire(file=filename,size=file_size)
615+
616+ invalid_size: if (file_size<0) then
617+
618+ allocate(character(len=0) :: file)
619+ err0 = state_type('get_file',STDLIB_IO_ERROR,filename,'has invalid size=',file_size)
620+ call err0%handle(err)
621+ return
622+
623+ endif invalid_size
624+
625+ ! Read file
626+ open(newunit=lun,file=filename, &
627+ form='unformatted',action='read',access='stream',status='old', &
628+ iostat=iostat,iomsg=iomsg)
629+
630+ if (iostat/=0) then
631+ allocate(character(len=0) :: file)
632+ err0 = state_type('get_file',STDLIB_IO_ERROR,'Cannot open',filename,'for read:',iomsg)
633+ call err0%handle(err)
634+ return
635+ end if
636+
637+ allocate(character(len=file_size) :: file)
638+
639+ read_data: if (file_size>0) then
640+
641+ read(lun, pos=1, iostat=iostat, iomsg=iomsg) file
642+
643+ ! Read error
644+ if (iostat/=0) then
645+
646+ inquire(unit=lun,pos=errpos)
647+ err0 = state_type('get_file',STDLIB_IO_ERROR,iomsg,'(',filename,'at byte',errpos,')')
648+ call err0%handle(err)
649+ return
650+
651+ endif
652+
653+ end if read_data
654+
655+ if (want_deleted) then
656+ close(lun,iostat=iostat,status='delete')
657+ if (iostat/=0) err0 = state_type('get_file',STDLIB_IO_ERROR,'Cannot delete',filename,'after reading')
658+ else
659+ close(lun,iostat=iostat)
660+ if (iostat/=0) err0 = state_type('get_file',STDLIB_IO_ERROR,'Cannot close',filename,'after reading')
661+ endif
662+
663+ ! Process output
664+ call err0%handle(err)
665+
666+ end subroutine get_file_char
530667
531668end module stdlib_io
0 commit comments