OSDN Git Service

PR testsuite/51875
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / coarray_21.f90
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=single" }
3 !
4 ! PR fortran/18918
5 !
6 ! Before scalar coarrays weren't regarded as scalar in the ME.
7 !
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
16
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
25
26
27 ! { dg-final { cleanup-modules "mod_reduction" } }