@@ -9,7 +9,7 @@ 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
1515 use stdlib_string_type, only : string_type
@@ -18,6 +18,25 @@ module stdlib_io
1818 ! Public API
1919 public :: loadtxt, savetxt, open, getline
2020
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#getfile-read-a-whole-ascii-file-into-a-string-variable))
25+ !!
26+ !!### Summary
27+ !! Function interface for reading the content of a file into a string.
28+ !!
29+ !!### Description
30+ !!
31+ !! This function 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+ public :: getfile
39+
2140 ! Private API that is exposed so that we can test it in tests
2241 public :: parse_mode
2342
@@ -528,4 +547,96 @@ contains
528547 call getline(input_unit, line, iostat, iomsg)
529548 end subroutine getline_input_string
530549
550+ !> Version: experimental
551+ !>
552+ !> Reads a whole ASCII file and loads its contents into a string variable.
553+ !> The function handles error states and optionally deletes the file after reading.
554+ type(string_type) function getfile(fileName,err,delete) result(file)
555+ !> Input file name
556+ character(*), intent(in) :: fileName
557+ !> [optional] State return flag. On error, if not requested, the code will stop.
558+ type(state_type), optional, intent(out) :: err
559+ !> [optional] Delete file after reading? Default: do not delete
560+ logical, optional, intent(in) :: delete
561+
562+ ! Local variables
563+ type(state_type) :: err0
564+ character(len=:), allocatable :: fileString
565+ character(len=512) :: iomsg
566+ integer :: lun,iostat
567+ integer(int64) :: errpos,fileSize
568+ logical :: is_present,want_deleted
569+
570+ ! Initializations
571+ file = ""
572+
573+ !> Check if the file should be deleted after reading
574+ if (present(delete)) then
575+ want_deleted = delete
576+ else
577+ want_deleted = .false.
578+ end if
579+
580+ !> Check file existing
581+ inquire(file=fileName, exist=is_present)
582+ if (.not.is_present) then
583+ err0 = state_type('getfile',STDLIB_IO_ERROR,'File not present:',fileName)
584+ call err0%handle(err)
585+ return
586+ end if
587+
588+ !> Retrieve file size
589+ inquire(file=fileName,size=fileSize)
590+
591+ invalid_size: if (fileSize<0) then
592+
593+ err0 = state_type('getfile',STDLIB_IO_ERROR,fileName,'has invalid size=',fileSize)
594+ call err0%handle(err)
595+ return
596+
597+ endif invalid_size
598+
599+ ! Read file
600+ open(newunit=lun,file=fileName, &
601+ form='unformatted',action='read',access='stream',status='old', &
602+ iostat=iostat,iomsg=iomsg)
603+
604+ if (iostat/=0) then
605+ err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot open',fileName,'for read:',iomsg)
606+ call err0%handle(err)
607+ return
608+ end if
609+
610+ allocate(character(len=fileSize) :: fileString)
611+
612+ read_data: if (fileSize>0) then
613+
614+ read(lun, pos=1, iostat=iostat, iomsg=iomsg) fileString
615+
616+ ! Read error
617+ if (iostat/=0) then
618+
619+ inquire(unit=lun,pos=errpos)
620+ err0 = state_type('getfile',STDLIB_IO_ERROR,iomsg,'(',fileName,'at byte',errpos,')')
621+ call err0%handle(err)
622+ return
623+
624+ endif
625+
626+ end if read_data
627+
628+ if (want_deleted) then
629+ close(lun,iostat=iostat,status='delete')
630+ if (iostat/=0) err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot delete',fileName,'after reading')
631+ else
632+ close(lun,iostat=iostat)
633+ if (iostat/=0) err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot close',fileName,'after reading')
634+ endif
635+
636+ ! Process output
637+ call move(from=fileString,to=file)
638+ call err0%handle(err)
639+
640+ end function getfile
641+
531642end module stdlib_io
0 commit comments