2 ! { dg-options "-fmax-errors=1000 -fcoarray=single" }
11 procedure(sub
), pointer :: ppc
13 procedure
:: tbp
=> sub
16 class(t
), allocatable
:: poly
20 class(t
), intent(in
) :: this
24 subroutine procTest(y
,z
)
34 call x
[1]%tbp
! OK, not polymorphic
36 call x
[1]%ppc
! { dg-error "Coindexed procedure-pointer component" }
41 call y
[1]%tbp
! OK, coindexed polymorphic object but not poly. subobj.
42 call y
[1]%ppc
! { dg-error "Coindexed procedure-pointer component" }
46 call z
%poly
%ppc() ! OK
47 call z
%poly
%tbp() ! OK
48 call z
[1]%poly
%tbp
! { dg-error "Polymorphic subobject of coindexed" }
49 call z
[1]%poly
%ppc
! { dg-error "Coindexed procedure-pointer component" }
50 end subroutine procTest
61 integer, allocatable
:: a
[:]
62 type(t1
), allocatable
:: b
[:]
63 type(t2
), allocatable
:: c
[:]
67 integer, intent(inout
) :: x
73 type(t
), intent(inout
) :: x
74 integer, target
:: tgt1
76 x
%a
[6] = 9 ! { dg-error "Assignment to coindexed variable" }
78 x
%b
[1]%p
=> tgt1
! { dg-error "shall not have a coindex" }
79 x
%b
%p
=> x
%b
[1]%p
! { dg-error "shall not have a coindex" }
80 x
%b
= t1(x
%b
[1]%p
) ! { dg-error "Coindexed expression to pointer component" }
81 x
%b
= x
%b
[1] ! { dg-error "derived type variable with a POINTER component in a PURE" }
82 call p2 (x
%c
[1]%i
) ! { dg-error "Coindexed actual argument" }
83 call p3 (x
%b
[1]%p
) ! { dg-error "to pointer dummy" }
86 type(t1
), save :: a
[*]
87 type(t2
), save :: b
[*]
88 integer, target
:: tgt1
90 a
[1]%p
=> tgt1
! { dg-error "shall not have a coindex" }
91 a
%p
=> a
[2]%p
! { dg-error "shall not have a coindex" }
92 a
= t1(a
[1]%p
) ! { dg-error "Coindexed expression to pointer component" }
94 call p2 (a
[1]%p
) ! OK - pointer target and not pointer
101 integer, allocatable
:: a(:)
108 x
[1]%a
= [ 1, 2, 3] ! OK - if shapes are the same, otherwise wrong
109 ! (no reallocate on assignment)
110 end subroutine assign
111 subroutine assign2(x
,y
)
112 type(t
),allocatable
:: x
[:]
115 x
[1] = y
! { dg-error "must not be have an allocatable ultimate component" }
116 end subroutine assign2
130 integer, save :: x
[*]
131 integer, save :: y(1)[*]
132 character(len
=20), save :: z
[*]
134 call t1(x
) ! { dg-error "Rank mismatch" }
135 call t1(x
[1]) ! { dg-error "Rank mismatch" }
138 call t1(y(1)[1]) ! { dg-error "Rank mismatch" }
141 call t3(z
[1]) ! { dg-error "Rank mismatch" }
148 DATA i
/(i
, i
=1,2)/ ! { dg-error "Expected PARAMETER symbol" }
149 do i
= 1, 5 ! { dg-error "cannot be a sub-component" }
150 end do ! { dg-error "Expecting END SUBROUTINE" }
154 integer, save :: x
[*]
156 DATA i
/(x
, x
=1,2)/ ! { dg-error "Expected PARAMETER symbol" }
157 do x
= 1, 5 ! { dg-error "cannot be a coarray" }
158 end do ! { dg-error "Expecting END SUBROUTINE" }
164 procedure(), pointer, nopass
:: ppt
=> null()
167 type(t
), save :: x
[*]
169 x
[1]%ppt
=> foo
! { dg-error "shall not have a coindex" }
174 integer, allocatable
:: a
[:,:]
176 call two(a
) ! { dg-error "Corank mismatch in argument" }
182 integer, allocatable
:: x
[:]
184 end subroutine corank
186 subroutine assign42()
187 integer, allocatable
:: z(:)[:]
189 end subroutine assign42
191 ! { dg-final { cleanup-modules "mod2 m mmm3 mmm4" } }