2 ! { dg-options "-fcoarray=single" }
6 subroutine cont1(x
) ! { dg-error "has the CONTIGUOUS attribute but is not an array pointer or an assumed-shape or assumed-rank array" }
9 class(t
), contiguous
, allocatable
:: x(:)
12 subroutine cont2(x
) ! { dg-error "has the CONTIGUOUS attribute but is not an array pointer or an assumed-shape or assumed-rank array" }
15 class(t
), contiguous
, allocatable
:: x(:)[:]
18 subroutine cont3(x
, y
)
21 class(t
), contiguous
, pointer :: x(:)
22 class(t
), contiguous
:: y(:)
25 function func() ! { dg-error "shall not be a coarray or have a coarray component" }
28 class(t
), allocatable
:: func
[*]
31 function func2() ! { dg-error "must be dummy, allocatable or pointer" }
33 integer, allocatable
:: caf
[:]
35 class(t
) :: func2a
! { dg-error "CLASS variable 'func2a' at .1. must be dummy, allocatable or pointer" }
39 subroutine foo1(x1
) ! { dg-error "Coarray variable 'x1' at .1. shall not have codimensions with deferred shape" }
45 subroutine foo2(x2
) ! { dg-error "Coarray variable 'x2' at .1. shall not have codimensions with deferred shape" }
54 subroutine foo3(x1
) ! { dg-error "Coarray variable 'x1' at .1. shall not have codimensions with deferred shape" }
60 subroutine foo4(x2
) ! { dg-error "Coarray variable 'x2' at .1. shall not have codimensions with deferred shape" }
69 subroutine bar1(y1
) ! { dg-error "Allocatable coarray variable 'y1' at .1. must have deferred shape" }
72 type(t
), allocatable
:: y1(:)[5:*]
75 subroutine bar2(y2
) ! { dg-error "Allocatable coarray variable 'y2' at .1. must have deferred shape" }
78 type(t
), allocatable
:: y2
[5:*]
81 subroutine bar3(z1
) ! { dg-error "Allocatable coarray variable 'z1' at .1. must have deferred shape" }
84 type(t
), allocatable
:: z1(5)[:]
87 subroutine bar4(z2
) ! { dg-error "Allocatable array 'z2' at .1. must have a deferred shape" }
90 type(t
), allocatable
:: z2(5)
93 subroutine bar5(z3
) ! { dg-error "Array pointer 'z3' at .1. must have a deferred shape" }
96 type(t
), pointer :: z3(5)
104 subroutine bar1c(y1
) ! { dg-error "Allocatable coarray variable 'y1' at .1. must have deferred shape" }
107 class(t
), allocatable
:: y1(:)[5:*]
110 subroutine bar2c(y2
) ! { dg-error "Allocatable coarray variable 'y2' at .1. must have deferred shape" }
113 class(t
), allocatable
:: y2
[5:*]
116 subroutine bar3c(z1
) ! { dg-error "Allocatable coarray variable 'z1' at .1. must have deferred shape" }
119 class(t
), allocatable
:: z1(5)[:]
122 subroutine bar4c(z2
) ! { dg-error "Allocatable array 'z2' at .1. must have a deferred shape" }
125 class(t
), allocatable
:: z2(5)
128 subroutine bar5c(z3
) ! { dg-error "Array pointer 'z3' at .1. must have a deferred shape" }
131 class(t
), pointer :: z3(5)
139 class(t
), allocatable
:: b(:)
162 subroutine inter2(x
) ! { dg-error "must have a deferred shape" }
163 class(t
), pointer :: x(5)
164 end subroutine inter2