view gcc/testsuite/gfortran.dg/namelist_93.f90 @ 144:8f4e72ab4e11

fix segmentation fault caused by nothing next cur_op to end
author Takahiro SHIMIZU <anatofuz@cr.ie.u-ryukyu.ac.jp>
date Sun, 23 Dec 2018 21:23:56 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
! PR78659 Spurious "requires DTIO" reported against namelist statement
MODULE ma
  IMPLICIT NONE
  TYPE :: ta
    INTEGER, allocatable :: array(:)
  END TYPE ta
END MODULE ma

PROGRAM p
  USE ma
  class(ta), allocatable :: x
  NAMELIST /nml/ x
  WRITE (*, nml)! { dg-error "is polymorphic and requires a defined input/output procedure" }
  READ (*, nml) ! { dg-error "is polymorphic and requires a defined input/output procedure" }
END PROGRAM p