1! { dg-do compile }
2! { dg-options "-fcoarray=lib" }
3!
4! Valid code - but currently not implemented for -fcoarray=lib; single okay
5!
6subroutine one
7implicit none
8type t
9  integer, allocatable :: a
10  integer :: b
11end type t
12type t2
13  type(t), allocatable :: caf2[:]
14end type t2
15type(t), save :: caf[*],x
16type(t2) :: y
17
18x = caf[4]     ! { dg-error "Sorry, coindexed coarray at \\(1\\) with allocatable component is not yet supported" }
19x%a = caf[4]%a ! { dg-error "Sorry, coindexed access to a pointer or allocatable component of the coindexed coarray at \\(1\\) is not yet supported" }
20x%b = caf[4]%b ! OK
21x = y%caf2[5]  ! { dg-error "Sorry, coindexed coarray at \\(1\\) with allocatable component is not yet supported" }
22x%a = y%caf2[4]%a ! { dg-error "Sorry, coindexed access to a pointer or allocatable component of the coindexed coarray at \\(1\\) is not yet supported" }
23x%b = y%caf2[4]%b ! OK
24end subroutine one
25
26subroutine two
27implicit none
28type t
29  integer, pointer :: a
30  integer :: b
31end type t
32type t2
33  type(t), allocatable :: caf2[:]
34end type t2
35type(t), save :: caf[*],x
36type(t2) :: y
37
38x = caf[4]     ! OK
39x%a = caf[4]%a ! { dg-error "Sorry, coindexed access to a pointer or allocatable component of the coindexed coarray at \\(1\\) is not yet supported" }
40x%b = caf[4]%b ! OK
41x = y%caf2[5]  ! OK
42x%a = y%caf2[4]%a ! { dg-error "Sorry, coindexed access to a pointer or allocatable component of the coindexed coarray at \\(1\\) is not yet supported" }
43x%b = y%caf2[4]%b ! OK
44end subroutine two
45
46subroutine three
47implicit none
48type t
49  integer :: b
50end type t
51type t2
52  type(t), allocatable :: caf2(:)[:]
53end type t2
54type(t), save :: caf(10)[*]
55integer :: x(10)
56type(t2) :: y
57
58x(1) = caf(2)[4]%b ! OK
59x(:) = caf(:)[4]%b ! { dg-error "Sorry, coindexed access at \\(1\\) to a scalar component with an array partref is not yet supported" }
60
61x(1) = y%caf2(2)[4]%b ! OK
62x(:) = y%caf2(:)[4]%b ! { dg-error "Sorry, coindexed access at \\(1\\) to a scalar component with an array partref is not yet supported" }
63end subroutine three
64
65subroutine four
66implicit none
67type t
68  integer, allocatable :: a
69  integer :: b
70end type t
71type t2
72  class(t), allocatable :: caf2[:]
73end type t2
74class(t), allocatable :: caf[:]
75type(t) :: x
76type(t2) :: y
77
78!x = caf[4]    ! Unsupported - and ICEs in resolve_ordinary_assign, cf. PR fortran/65397
79x%a = caf[4]%a ! { dg-error "Sorry, coindexed access to a pointer or allocatable component of the coindexed coarray at \\(1\\) is not yet supported" }
80x%b = caf[4]%b ! OK
81!x = y%caf2[5] ! Unsupported - and ICEs in resolve_ordinary_assign, cf. PR fortran/65397
82x%a = y%caf2[4]%a ! { dg-error "Sorry, coindexed access to a pointer or allocatable component of the coindexed coarray at \\(1\\) is not yet supported" }
83x%b = y%caf2[4]%b ! OK
84end subroutine four
85
86subroutine five
87implicit none
88type t
89  integer, pointer :: a
90  integer :: b
91end type t
92type t2
93  class(t), allocatable :: caf2[:]
94end type t2
95class(t), save, allocatable :: caf[:]
96type(t) :: x
97type(t2) :: y
98
99!x = caf[4]     ! OK - but ICEs in resolve_ordinary_assign, cf. PR fortran/65397
100x%a = caf[4]%a ! { dg-error "Sorry, coindexed access to a pointer or allocatable component of the coindexed coarray at \\(1\\) is not yet supported" }
101x%b = caf[4]%b ! OK
102!x = y%caf2[5]  ! OK - but ICEs in resolve_ordinary_assign, cf. PR fortran/65397
103x%a = y%caf2[4]%a ! { dg-error "Sorry, coindexed access to a pointer or allocatable component of the coindexed coarray at \\(1\\) is not yet supported" }
104x%b = y%caf2[4]%b ! OK
105end subroutine five
106
107subroutine six
108implicit none
109type t
110  integer :: b
111end type t
112type t2
113  class(t), allocatable :: caf2(:)[:]
114end type t2
115class(t), save, allocatable :: caf(:)[:]
116integer :: x(10)
117type(t2) :: y
118
119x(1) = caf(2)[4]%b ! OK
120x(:) = caf(:)[4]%b ! { dg-error "Sorry, coindexed access at \\(1\\) to a scalar component with an array partref is not yet supported" }
121
122x(1) = y%caf2(2)[4]%b ! OK
123x(:) = y%caf2(:)[4]%b ! { dg-error "Sorry, coindexed access at \\(1\\) to a scalar component with an array partref is not yet supported" }
124end subroutine six
125