Skip to content

Procedure to read whole line to deferred length character #595

Closed
@awvwgk

Description

@awvwgk

Motivation

Just wrote a tutorial for using stdlib with fpm and noticed that I can't read a whole line into a deferred length character.

See: https://awvwgk.github.io/fpm-docs/en/tutorial/dependencies.html

Prior Art

For the tutorial I used the following snippet

  !> Read a whole line from a formatted unit into a deferred length character variable
  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 :: bufsize = 512
    character(len=bufsize) :: buffer, msg
    integer :: chunk, stat

    allocate(character(len=0) :: line)
    do
      read(unit, '(a)', advance='no', iostat=stat, iomsg=msg, size=chunk) buffer
      if (stat > 0) exit
      line = line // buffer(:chunk)
      if (stat < 0) then
        if (is_iostat_eor(stat)) stat = 0
        exit
      end if
    end do

    if (stat /= 0 .and. present(iomsg)) iomsg = trim(msg)
    iostat = stat
  end subroutine getline

Additional Information

Due to gcc#100875 and #354 I couldn't use string_type for the tutorial.

Metadata

Metadata

Assignees

No one assigned

    Labels

    easyDifficulty level is easy and good for starting into this projectgood first issueGood for newcomersideaProposition of an idea and opening an issue to discuss ittopic: IOCommon input/output related features

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions