2 ! { dg-options "-fmax-errors=1000 -fcoarray=single" }
11 integer, allocatable
:: a
17 integer, pointer :: ptr
18 integer, allocatable
:: alloc(:)
20 type(t
), target
:: i
[*]
21 type(t
), allocatable
:: ca
[:]
22 type(t4
), target
:: tt4
[*]
23 type(t4
), allocatable
:: ca2
[:]
24 integer, volatile :: volat
[*]
25 integer, asynchronous
:: async
[*]
26 integer :: caf1
[1,*], caf2
[*]
29 call foo(i
[1]%ptr
) ! { dg-error "Coindexed actual argument at .1. to pointer dummy" }
31 call bar(i
[1]%ptr
) ! OK, value of ptr target
32 call bar(i
[1]%alloc(1)) ! OK
33 call typeDummy(i
) ! OK
34 call typeDummy(i
[1]) ! { dg-error "with ultimate pointer component" }
35 call typeDummy2(ca
) ! OK
36 call typeDummy2(ca
[1]) ! { dg-error "with ultimate pointer component" }
37 call typeDummy3(tt4
%xt3
) ! OK
38 call typeDummy3(tt4
[1]%xt3
) ! { dg-error "requires either VALUE or INTENT.IN." }
39 call typeDummy4(ca2
) ! OK
40 call typeDummy4(ca2
[1]) ! { dg-error "requires INTENT.IN." }
41 ! Note: Checking an VOLATILE dummy is not possible as volatile + intent(in)
46 call asyn(volat
[1]) ! { dg-error "Coindexed ASYNCHRONOUS or VOLATILE actual argument" }
47 call asyn(async
[1]) ! { dg-error "Coindexed ASYNCHRONOUS or VOLATILE actual argument" }
49 call coarray(caf1
) ! rank mismatch; OK, for non allocatable coarrays
51 call coarray(caf2
[1]) ! { dg-error "must be a coarray" }
53 call ups(i
[1]) ! { dg-error "with ultimate pointer component" }
55 call ups(i
[1]%ptr
) ! OK - passes target not pointer
58 integer, intent(in
), asynchronous
:: a
68 end subroutine coarray
69 subroutine typeDummy(a
)
71 end subroutine typeDummy
72 subroutine typeDummy2(a
)
73 type(t
),allocatable
:: a
74 end subroutine typeDummy2
75 subroutine typeDummy3(a
)
77 end subroutine typeDummy3
78 subroutine typeDummy4(a
)
79 type(t4
), allocatable
:: a
80 end subroutine typeDummy4
86 integer, allocatable
:: a(:)
89 type(t
), allocatable
:: b(:)[:], C
[:]
91 allocate(b(1)) ! { dg-error "Coarray specification" }
92 allocate(a
[3]%a(5)) ! { dg-error "Coindexed allocatable" }
99 integer, save, target
:: a
[*]
101 data a
[1]/5/ ! { dg-error "cannot have a coindex" }
103 integer, pointer :: p
105 type(t
), save :: x
[*]
114 x
[1]%p
=> a
! { dg-error "shall not have a coindex" }
115 x
%p
=> a
[1] ! { dg-error "shall not have a coindex" }
116 end subroutine dataPtr
124 type(t
), save :: x
[*]
127 integer, save :: y(1)[*] !(1)
128 call sub(x(1:1)[1]) ! { dg-error "Rank mismatch" }
130 subroutine sub(a
) ! { dg-error "shall not have codimensions with deferred shape" }
137 integer, save :: i
[*]
140 call foo(j
) ! { dg-error "must be a coarray" }
148 subroutine allocateTest()
150 real, allocatable
, codimension
[:,:] :: a
,b
,c
154 allocate(a
[q
,*]) ! OK
155 allocate(b
[q
,*]) ! OK
156 allocate(c
[q
,*]) ! OK
157 end subroutine allocateTest
160 subroutine testAlloc4()
163 double precision, allocatable
:: array(:)
165 type(co_double_3
),save, codimension
[*] :: work
166 allocate(work
%array(1))
167 print *, size(work
%array
)
168 end subroutine testAlloc4
172 integer, save :: i
[*]
173 print *, i
[*] ! { dg-error "Coindex of codimension 1 must be a scalar" }