modula2: Simplify REAL/LONGREAL/SHORTREAL node creation.
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_poly_4.f90
blobff574c1ef650a2778b465fd3b139b267d0620171
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=lib -fdump-tree-original" }
4 subroutine test(i)
5 type t
6 real, allocatable :: x[:]
7 end type t
9 interface
10 subroutine sub(y)
11 import
12 real :: y[*]
13 end subroutine sub
14 end interface
16 integer :: i
17 type(t), save :: var
18 allocate(var%x[*])
19 call sub(var%x)
20 end subroutine test
22 ! { dg-final { scan-tree-dump-times "sub \\(\\(real\\(kind=4\\) \\*\\) var.x.data, var.x.token, 0\\);" 1 "original" } }