* tree-loop-distribution.c (struct partition): New field recording
[official-gcc.git] / gcc / testsuite / gfortran.dg / namelist_92.f90
blobfc678caacb7bbae1081234bfa10dc06814e47c49
1 ! { dg-do compile }
2 ! PR78659 Spurious "requires DTIO" reported against namelist statement
3 MODULE ma
4 IMPLICIT NONE
5 TYPE :: ta
6 INTEGER, allocatable :: array(:)
7 END TYPE ta
8 END MODULE ma
10 PROGRAM p
11 USE ma
12 type(ta):: x
13 NAMELIST /nml/ x
14 WRITE (*, nml) ! { dg-error "has ALLOCATABLE or POINTER components and thus requires a defined input/output" }
15 READ (*, nml) ! { dg-error "has ALLOCATABLE or POINTER components and thus requires a defined input/output" }
16 END PROGRAM p