modula2: Simplify REAL/LONGREAL/SHORTREAL node creation.
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_38.f90
blob04ef742faabb280edff308f356395f01c5061fc3
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=lib" }
4 ! Valid code - but currently not implemented for -fcoarray=lib; single okay
6 subroutine one
7 implicit none
8 type t
9 integer, allocatable :: a
10 integer :: b
11 end type t
12 type t2
13 type(t), allocatable :: caf2[:]
14 end type t2
15 type(t), save :: caf[*],x
16 type(t2) :: y
18 x = caf[4] ! OK, now
19 x%a = caf[4]%a ! OK, now
20 x%b = caf[4]%b ! OK
21 x = y%caf2[5] ! OK, now
22 x%a = y%caf2[4]%a ! OK, now
23 x%b = y%caf2[4]%b ! OK
24 end subroutine one
26 subroutine two
27 implicit none
28 type t
29 integer, pointer :: a
30 integer :: b
31 end type t
32 type t2
33 type(t), allocatable :: caf2[:]
34 end type t2
35 type(t), save :: caf[*],x
36 type(t2) :: y
38 x = caf[4] ! OK
39 x%a = caf[4]%a ! OK, now
40 x%b = caf[4]%b ! OK
41 x = y%caf2[5] ! OK
42 x%a = y%caf2[4]%a ! OK, now
43 x%b = y%caf2[4]%b ! OK
44 end subroutine two
46 subroutine three
47 implicit none
48 type t
49 integer :: b
50 end type t
51 type t2
52 type(t), allocatable :: caf2(:)[:]
53 end type t2
54 type(t), save :: caf(10)[*]
55 integer :: x(10)
56 type(t2) :: y
58 x(1) = caf(2)[4]%b ! OK
59 x(:) = caf(:)[4]%b ! OK now
61 x(1) = y%caf2(2)[4]%b ! OK
62 x(:) = y%caf2(:)[4]%b ! OK now
63 end subroutine three
65 subroutine four
66 implicit none
67 type t
68 integer, allocatable :: a
69 integer :: b
70 end type t
71 type t2
72 class(t), allocatable :: caf2[:]
73 end type t2
74 class(t), allocatable :: caf[:] ! { dg-error "Sorry, allocatable/pointer components in polymorphic" }
75 type(t) :: x
76 type(t2) :: y
78 !x = caf[4] ! Unsupported - and ICEs in resolve_ordinary_assign, cf. PR fortran/65397
79 x%a = caf[4]%a ! OK, now
80 x%b = caf[4]%b ! OK
81 !x = y%caf2[5] ! Unsupported - and ICEs in resolve_ordinary_assign, cf. PR fortran/65397
82 x%a = y%caf2[4]%a ! Ok, now
83 x%b = y%caf2[4]%b ! OK
84 end subroutine four
86 subroutine five
87 implicit none
88 type t
89 integer, pointer :: a
90 integer :: b
91 end type t
92 type t2
93 class(t), allocatable :: caf2[:]
94 end type t2
95 class(t), save, allocatable :: caf[:] ! { dg-error "Sorry, allocatable/pointer components in polymorphic" }
96 type(t) :: x
97 type(t2) :: y
99 !x = caf[4] ! OK - but ICEs in resolve_ordinary_assign, cf. PR fortran/65397
100 x%a = caf[4]%a ! OK, now
101 x%b = caf[4]%b ! OK
102 !x = y%caf2[5] ! OK - but ICEs in resolve_ordinary_assign, cf. PR fortran/65397
103 x%a = y%caf2[4]%a ! OK, now
104 x%b = y%caf2[4]%b ! OK
105 end subroutine five
107 subroutine six
108 implicit none
109 type t
110 integer :: b
111 end type t
112 type t2
113 class(t), allocatable :: caf2(:)[:]
114 end type t2
115 class(t), save, allocatable :: caf(:)[:]
116 integer :: x(10)
117 type(t2) :: y
119 x(1) = caf(2)[4]%b ! OK
120 x(:) = caf(:)[4]%b ! OK now
122 x(1) = y%caf2(2)[4]%b ! OK
123 x(:) = y%caf2(:)[4]%b ! OK now
124 end subroutine six
126 call one()
127 call two()
128 call three()
129 call four()
130 call five()
131 call six()