AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_poly_9.f90
blobea2a9422cebb040a91f7191dc09cc99fea66e2c6
1 ! { dg-do run }
2 ! { dg-options "-fcoarray=single" }
4 ! Test the fix for PR91726.
6 ! Contributed by Gerhardt Steinmetz <gscfq@t-online.de>
8 module m
9 type s
10 class(*), allocatable :: a[:] ! This ICEd
11 end type
12 type t
13 class(*), allocatable :: a(:)[:] ! This was OK
14 end type
15 end
17 use m
18 call foo
19 call bar
20 contains
21 subroutine foo
22 type (s) :: a
23 integer(4) :: i = 42_4
24 allocate (a%a[*], source = i) ! This caused runtime segfaults
25 select type (z => a%a) ! ditto
26 type is (integer(4))
27 if (z .ne. 42_4) stop 1
28 end select
29 end subroutine
30 subroutine bar ! Arrays always worked
31 type (t) :: a
32 allocate (a%a(3)[*], source = [1_4, 2_4, 3_4])
33 select type (z => a%a)
34 type is (integer(4))
35 if (any (z .ne. [1_4, 2_4, 3_4])) stop 2
36 end select
37 end subroutine
38 end