Skip to content

Commit 5b2dbb0

Browse files
committed
getfile: read all at once
1 parent 8788cc6 commit 5b2dbb0

File tree

1 file changed

+38
-35
lines changed

1 file changed

+38
-35
lines changed

src/stdlib_io.fypp

Lines changed: 38 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -558,16 +558,14 @@ contains
558558

559559
! Local variables
560560
type(state_type) :: err0
561-
integer, parameter :: buffer_len = 65536
562-
character(len=:), allocatable :: buffer,fileString
561+
character(len=:), allocatable :: fileString
563562
character(len=512) :: iomsg
564563
integer :: lun,iostat
565-
integer(8) :: mypos,oldpos,size_read
564+
integer(int64) :: errpos,fileSize
566565
logical :: is_present,want_deleted
567566

568567
! Initializations
569568
file = ""
570-
allocate(character(len=buffer_len) :: buffer)
571569

572570
!> Check if the file should be deleted after reading
573571
if (present(delete)) then
@@ -583,54 +581,59 @@ contains
583581
call err0%handle(err)
584582
return
585583
end if
586-
584+
585+
!> Retrieve file size
586+
inquire(file=fileName,size=fileSize)
587+
588+
invalid_size: if (fileSize<0) then
589+
590+
err0 = state_type('getfile',STDLIB_IO_ERROR,fileName,'has invalid size=',fileSize)
591+
call err0%handle(err)
592+
return
593+
594+
endif invalid_size
595+
596+
! Read file
587597
open(newunit=lun,file=fileName, &
588598
form='unformatted',action='read',access='stream',status='old', &
589599
iostat=iostat,iomsg=iomsg)
600+
590601
if (iostat/=0) then
591602
err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot open',fileName,'for read:',iomsg)
592603
call err0%handle(err)
593604
return
594-
end if
595-
596-
allocate(character(len=0)::fileString)
597-
read_by_chunks: do
598-
599-
! Read another buffer
600-
inquire(unit=lun,pos=oldpos)
601-
602-
read (lun, iostat=iostat, iomsg=iomsg) buffer
603-
604-
if (is_iostat_end(iostat) .or. is_iostat_eor(iostat)) then
605-
! Partial buffer read
606-
inquire(unit=lun,pos=mypos)
607-
size_read = mypos-oldpos
608-
fileString = fileString // buffer(:size_read)
609-
iostat = 0
610-
iomsg = ''
611-
exit read_by_chunks
612-
else if (iostat == 0) then
613-
! Full buffer read
614-
fileString = fileString // buffer
615-
else
616-
! Read error
617-
err0 = state_type('getfile',STDLIB_IO_ERROR,'Error reading',fileName,'at character',oldpos)
618-
exit read_by_chunks
619-
end if
620-
end do read_by_chunks
621-
605+
end if
606+
607+
allocate(character(len=fileSize) :: fileString)
608+
609+
read_data: if (fileSize>0) then
610+
611+
read(lun, pos=1, iostat=iostat, iomsg=iomsg) fileString
612+
613+
! Read error
614+
if (iostat/=0) then
615+
616+
inquire(unit=lun,pos=errpos)
617+
err0 = state_type('getfile',STDLIB_IO_ERROR,'Error reading',fileName,'at byte',errpos)
618+
call err0%handle(err)
619+
return
620+
621+
endif
622+
623+
end if read_data
624+
622625
if (want_deleted) then
623626
close(lun,iostat=iostat,status='delete')
624627
if (iostat/=0) err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot delete',fileName,'after reading')
625628
else
626629
close(lun,iostat=iostat)
627630
if (iostat/=0) err0 = state_type('getfile',STDLIB_IO_ERROR,'Cannot close',fileName,'after reading')
628-
endif
631+
endif
629632

630633
! Process output
631634
call move(from=fileString,to=file)
632635
call err0%handle(err)
633636

634-
end function getfile
637+
end function getfile
635638

636639
end module stdlib_io

0 commit comments

Comments
 (0)