AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / pointer_assign_9.f90
blob5643235ff23beb0ea2e06e349cf68be7335aab26
1 ! { dg-do run }
3 ! PR fortran/57530
6 ! TYPE => CLASS pointer assignment for functions
8 module m
9 implicit none
10 type t
11 integer :: ii = 55
12 end type t
13 contains
14 function f1()
15 class(t), pointer :: f1
16 allocate (f1)
17 f1%ii = 123
18 end function f1
19 function f2()
20 class(t), pointer :: f2(:)
21 allocate (f2(3))
22 f2(:)%ii = [-11,-22,-33]
23 end function f2
24 end module m
26 program test
27 use m
28 implicit none
29 type(t), pointer :: p1, p2(:),p3(:,:)
30 p1 => f1()
31 if (p1%ii /= 123) STOP 1
32 p2 => f2()
33 if (any (p2%ii /= [-11,-22,-33])) STOP 2
34 p3(2:2,1:3) => f2()
35 if (any (p3(2,:)%ii /= [-11,-22,-33])) STOP 3
36 end program test