@@ -11,10 +11,11 @@ module stdlib_io
1111  use stdlib_error, only: error_stop
1212  use stdlib_optval, only: optval
1313  use stdlib_ascii, only: is_blank
14+   use stdlib_string_type, only : string_type
1415  implicit none
1516  private
1617  ! Public API
17-   public :: loadtxt, savetxt, open
18+   public :: loadtxt, savetxt, open, getline 
1819
1920  ! Private API that is exposed so that we can test it in tests
2021  public :: parse_mode
@@ -31,6 +32,14 @@ module stdlib_io
3132    FMT_COMPLEX_XDP = '(*(es26.18e3,1x,es26.18e3))', &
3233    FMT_COMPLEX_QP = '(*(es44.35e4,1x,es44.35e4))'
3334
35+   !> Version: experimental
36+   !>
37+   !> Read a whole line from a formatted unit into a string variable
38+   interface getline
39+     module procedure :: getline_char
40+     module procedure :: getline_string
41+   end interface getline
42+ 
3443  interface loadtxt
3544    !! version: experimental
3645    !!
@@ -331,4 +340,59 @@ contains
331340
332341  end function parse_mode
333342
343+   !> Version: experimental
344+   !>
345+   !> Read a whole line from a formatted unit into a deferred length character variable
346+   subroutine getline_char(unit, line, iostat, iomsg)
347+     !> Formatted IO unit
348+     integer, intent(in) :: unit
349+     !> Line to read
350+     character(len=:), allocatable, intent(out) :: line
351+     !> Status of operation
352+     integer, intent(out), optional :: iostat
353+     !> Error message
354+     character(len=:), allocatable, optional :: iomsg
355+ 
356+     integer, parameter :: bufsize = 512
357+     character(len=bufsize) :: buffer, msg
358+     integer :: chunk, stat
359+ 
360+     allocate(character(len=0) :: line)
361+     do
362+       read(unit, '(a)', advance='no', iostat=stat, iomsg=msg, size=chunk) buffer
363+       if (stat > 0) exit
364+       line = line // buffer(:chunk)
365+       if (stat < 0) then
366+         if (is_iostat_eor(stat)) stat = 0
367+         exit
368+       end if
369+     end do
370+ 
371+     if (stat /= 0 .and. present(iomsg)) iomsg = trim(msg)
372+     if (present(iostat)) then
373+       iostat = stat
374+     else if (stat /= 0) then
375+       call error_stop(trim(msg))
376+     end if
377+   end subroutine getline_char
378+ 
379+   !> Version: experimental
380+   !>
381+   !> Read a whole line from a formatted unit into a string variable
382+   subroutine getline_string(unit, line, iostat, iomsg)
383+     !> Formatted IO unit
384+     integer, intent(in) :: unit
385+     !> Line to read
386+     type(string_type), intent(out) :: line
387+     !> Status of operation
388+     integer, intent(out), optional :: iostat
389+     !> Error message
390+     character(len=:), allocatable, optional :: iomsg
391+ 
392+     character(len=:), allocatable :: buffer
393+ 
394+     call getline(unit, buffer, iostat, iomsg)
395+     line = string_type(buffer)
396+   end subroutine getline_string
397+ 
334398end module stdlib_io
0 commit comments