view gcc/testsuite/gfortran.dg/namelist_92.f90 @ 145:1830386684a0

gcc-9.2.0
author anatofuz
date Thu, 13 Feb 2020 11:34:05 +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
  type(ta):: x
  NAMELIST /nml/ x
  WRITE (*, nml) ! { dg-error "has ALLOCATABLE or POINTER components and thus requires a defined input/output" }
  READ (*, nml) ! { dg-error "has ALLOCATABLE or POINTER components and thus requires a defined input/output" }
END PROGRAM p