getline(3f) - [M_io:READ] read a line of arbintrary length from specified
 LUN into allocatable string (up to system line length limit)
(LICENSE:PD)
subroutine getline(unit,line,iostat,iomsg)
integer,intent(in)                       :: unit
character(len=:),allocatable,intent(out) :: line
integer,intent(out)                      :: iostat
character(len=:), allocatable, optional  :: iomsg
Read a line of any length up to programming environment maximum
line length. Requires Fortran 2003+.
It is primarily expected to be used when reading input which will
then be parsed or echoed.
The input file must have a PAD attribute of YES for the function
to work properly, which is typically true.
The simple use of a loop that repeatedly re-allocates a character
variable in addition to reading the input file one buffer at a
time could (depending on the programming environment used) be
inefficient, as it could reallocate and allocate memory used for
the output string with each buffer read.
LINE    The line read when IOSTAT returns as zero.
LUN     LUN (Fortran logical I/O unit) number of file open and ready
        to read.
IOSTAT  status returned by READ(IOSTAT=IOS). If not zero, an error
        occurred or an end-of-file or end-of-record was encountered.
IOMSG   error message returned by system when IOSTAT is not zero.
Sample program:
program demo_getline
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit
use,intrinsic :: iso_fortran_env, only : iostat_end
use FPM_filesystem, only : getline
implicit none
integer :: iostat
character(len=:),allocatable :: line, iomsg
   open(unit=stdin,pad='yes')
   INFINITE: do
      call getline(stdin,line,iostat,iomsg)
      if(iostat /= 0) exit INFINITE
      write(*,'(a)')'['//line//']'
   enddo INFINITE
   if(iostat /= iostat_end)then
      write(*,*)'error reading input:',iomsg
   endif
end program demo_getline
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| integer, | intent(in) | :: | unit | Formatted IO unit | ||
| character(len=:), | intent(out), | allocatable | :: | line | Line to read | |
| integer, | intent(out) | :: | iostat | Status of operation | ||
| character(len=:), | optional, | allocatable | :: | iomsg | Error message | 
subroutine getline(unit, line, iostat, iomsg) !> Formatted IO unit integer, intent(in) :: unit !> Line to read character(len=:), allocatable, intent(out) :: line !> Status of operation integer, intent(out) :: iostat !> Error message character(len=:), allocatable, optional :: iomsg integer, parameter :: BUFFER_SIZE = 1024 character(len=BUFFER_SIZE) :: buffer character(len=256) :: msg integer :: size integer :: stat allocate(character(len=0) :: line) do read(unit, '(a)', advance='no', iostat=stat, iomsg=msg, size=size) & & buffer if (stat > 0) exit line = line // buffer(:size) if (stat < 0) then if (is_iostat_eor(stat)) then stat = 0 end if exit end if end do if (stat /= 0) then if (present(iomsg)) iomsg = trim(msg) end if iostat = stat end subroutine getline