re PR fortran/78741 (ICE in gfc_get_symbol_decl, at fortran/trans-decl.c:1534)
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray / subobject_1.f90
blob9ada95849e49b0b7dd5fdda251ff3f3b33b695dd
1 ! { dg-do run }
3 ! PR fortran/50420
4 ! Coarray subobjects were not accepted as valid coarrays
6 integer :: i
7 integer, parameter :: la = 4, lb = 5, lc = 8
8 integer, parameter :: init(la) = -4 + (/ (i, i=1,la) /)
10 type t
11 integer :: i
12 end type t
13 type t2
14 type(t), allocatable :: a[:]
15 end type t2
16 type t3
17 type(t), allocatable :: a(:)[:]
18 end type t3
20 type(t2) :: b
21 type(t3) :: c
23 allocate(b%a[lb:*])
24 b%a%i = 7
25 if (b%a%i /= 7) STOP 1
26 if (any (lcobound(b%a) /= (/ lb /))) STOP 2
27 if (ucobound(b%a, dim=1) /= num_images() + lb - 1) STOP 3
28 if (any (lcobound(b%a%i) /= (/ lb /))) STOP 4
29 if (ucobound(b%a%i, dim=1) /= num_images() + lb - 1) STOP 5
30 allocate(c%a(la)[lc:*])
31 c%a%i = init
32 if (any(c%a%i /= init)) STOP 6
33 if (any (lcobound(c%a) /= (/ lc /))) STOP 7
34 if (ucobound(c%a, dim=1) /= num_images() + lc - 1) STOP 8
35 if (any (lcobound(c%a%i) /= (/ lc /))) STOP 9
36 if (ucobound(c%a%i, dim=1) /= num_images() + lc - 1) STOP 10
37 if (c%a(2)%i /= init(2)) STOP 11
38 if (any (lcobound(c%a(2)) /= (/ lc /))) STOP 12
39 if (ucobound(c%a(2), dim=1) /= num_images() + lc - 1) STOP 13
40 if (any (lcobound(c%a(2)%i) /= (/ lc /))) STOP 14
41 if (ucobound(c%a(2)%i, dim=1) /= num_images() + lc - 1) STOP 15
42 deallocate(b%a, c%a)
43 end