https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78661

--- Comment #27 from Jerry DeLisle <jvdelisle at gcc dot gnu.org> ---
With the patch applied and the following test case:

MODULE m
  IMPLICIT NONE
  TYPE :: t
    integer :: j
    CHARACTER :: c
    integer :: k
  CONTAINS
    PROCEDURE :: write_formatted
    GENERIC :: WRITE(FORMATTED) => write_formatted
    PROCEDURE :: read_formatted
    GENERIC :: READ(FORMATTED) => read_formatted
  END TYPE
CONTAINS
  SUBROUTINE write_formatted(dtv, unit, iotype, v_list, iostat, iomsg)
    CLASS(t), INTENT(IN) :: dtv
    INTEGER, INTENT(IN) :: unit
    CHARACTER(*), INTENT(IN) :: iotype
    INTEGER, INTENT(IN) :: v_list(:)
    INTEGER, INTENT(OUT) :: iostat
    CHARACTER(*), INTENT(INOUT) :: iomsg
    WRITE (unit, "(i10,3x,A,3x,i10)", IOSTAT=iostat, IOMSG=iomsg) dtv%j, dtv%c,
dtv%k
  END SUBROUTINE
  SUBROUTINE read_formatted(dtv, unit, iotype, v_list, iostat, iomsg)
    CLASS(t), INTENT(INOUT) :: dtv
    INTEGER, INTENT(IN) :: unit
    CHARACTER(*), INTENT(IN) :: iotype
    INTEGER, INTENT(IN) :: v_list(:)
    INTEGER, INTENT(OUT) :: iostat
    CHARACTER(*), INTENT(INOUT) :: iomsg
    READ (unit, "(i10,3x,A,3x,i10)", IOSTAT=iostat, IOMSG=iomsg) dtv%j, dtv%c,
dtv%k
  END SUBROUTINE read_formatted
END MODULE

PROGRAM p
  USE m
  IMPLICIT NONE
  class(t), allocatable :: x
  NAMELIST /nml/ x
  x = t(55,'a',42)
  WRITE (10, nml)
  REWIND(10)
  READ(10, nml)
END

On the write I see what I expect, but we need to adjust list_read.c to handle
the parsing of input correctly.

$ ./a.out 
At line 42 of file 1test.f03 (unit = 10, file = 'fort.10')
Fortran runtime error: namelist read: misplaced = sign
$ cat fort.10 
&NML
 X=        55   a           42
 /

Reply via email to