2017-12-08 Richard Biener <rguenther@suse.de>
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_21.f90
blobe805cf68a0f09eff24cab1940d915e0c258e01be
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=single" }
4 ! PR fortran/18918
6 ! Before scalar coarrays weren't regarded as scalar in the ME.
8 module mod_reduction
9 real :: g[*]
10 contains
11 subroutine caf_reduce(x)
12 real, intent(in) :: x
13 g = x ! << used to ICE
14 end
15 end module
17 program test
18 integer, parameter :: size = 4000
19 type :: pct
20 integer, allocatable :: data(:,:)
21 end type
22 type(pct) :: picture[*]
23 allocate(picture%data(size, size))
24 end program test