Merge from mainline (167278:168000).
[official-gcc/graphite-test-results.git] / gcc / testsuite / gfortran.dg / alloc_comp_basics_4.f90
blob508d5670689f03243310a51a73f23e9be5fabe54
1 ! { dg-do compile }
2 ! Tests the fix for PR30660 in which gfortran insisted that g_dest
3 ! should have the SAVE attribute because the hidden default
4 ! initializer for the allocatable component was being detected.
6 ! Contributed by Toon Moene <toon@moene.indiv.nluug.nl>
8 MODULE types_m
9 TYPE coord_t
10 INTEGER ncord
11 REAL,ALLOCATABLE,DIMENSION(:) :: x, y
12 END TYPE
14 TYPE grib_t
15 REAL,DIMENSION(:),ALLOCATABLE :: vdata
16 TYPE(coord_t) coords
17 END TYPE
18 END MODULE
20 MODULE globals_m
21 USE types_m
22 TYPE(grib_t) g_dest ! output field
23 END MODULE
24 ! { dg-final { cleanup-modules "types_m globals_m" } }