2 ! { dg-options "-fcoarray=single" }
6 ! CONTIGUOUS compile-time tests
9 ! C448: Must be an array with POINTER attribute
11 integer, contiguous
:: ca(5) ! { dg-error "Component .ca. at .1. has the CONTIGUOUS" }
14 integer, contiguous
, allocatable
:: cb(:) ! { dg-error "Component .cb. at .1. has the CONTIGUOUS" }
17 integer, contiguous
, pointer :: cc(:) ! OK
20 integer, pointer, contiguous
:: cd
! { dg-error "Component .cd. at .1. has the CONTIGUOUS" }
24 ! C530: Must be an array and (a) a POINTER or (b) assumed shape.
26 integer, pointer :: x(:)
27 integer, intent(in
) :: y(:)
30 integer, contiguous
:: a(5) ! { dg-error ".a. at .1. has the CONTIGUOUS attribute" }
31 integer, contiguous
, allocatable
:: b(:) ! { dg-error ".b. at .1. has the CONTIGUOUS attribute" }
32 integer, contiguous
, pointer :: c(:) ! OK
33 integer, pointer, contiguous
:: d
! { dg-error ".d. at .1. has the CONTIGUOUS attribute" }
36 ! Pointer assignment check:
37 ! If the pointer object has the CONTIGUOUS attribute, the pointer target shall be contiguous.
38 ! Note: This is not compile-time checkable; but F2008, 5.3.7 except in a very few cases.
39 subroutine ptr_assign()
40 integer, pointer, contiguous
:: ptr1(:)
41 integer, target
:: tgt(5)
46 ! C1239 (R1223) If an actual argument is a nonpointer array that has the ASYNCHRONOUS or VOLATILE
47 ! attribute but is not simply contiguous (6.5.4), and the corresponding dummy argument has either the
48 ! VOLATILE or ASYNCHRONOUS attribute, that dummy argument shall be an assumed-shape array
49 ! that does not have the CONTIGUOUS attribute.
55 type(t
), volatile :: f
56 integer, asynchronous
:: a(4), b(4)
57 integer, volatile :: c(4), d(4)
58 call test (a
,b
,c
) ! OK
59 call test (a
,b(::2),c
) ! { dg-error "array without CONTIGUOUS" }
60 call test (a(::2),b
,c
) ! { dg-error "array without CONTIGUOUS" }
62 call test (a
,b
,f
%e
) ! OK
63 call test (a
,f
%e
,c
) ! OK
64 call test (f
%e
,b
,c
) ! OK
65 call test (a
,b
,f
%e(::2)) ! OK
66 call test (a
,f
%e(::2),c
) ! { dg-error "array without CONTIGUOUS" }
67 call test (f
%e(::2),b
,c
) ! { dg-error "array without CONTIGUOUS" }
69 subroutine test(u
, v
, w
)
70 integer, asynchronous
:: u(:), v(*)
71 integer, volatile :: w(:)
77 ! C1240 (R1223) If an actual argument is an array pointer that has the ASYNCHRONOUS or VOLATILE
78 ! attribute but does not have the CONTIGUOUS attribute, and the corresponding dummy argument has
79 ! either the VOLATILE or ASYNCHRONOUS attribute, that dummy argument shall be an array pointer
80 ! or an assumed-shape array that does not have the CONTIGUOUS attribute.
84 integer,pointer :: e(:)
86 type(t
), volatile :: f
87 integer, pointer, asynchronous
:: a(:), b(:)
88 integer,pointer, volatile :: c(:), d(:)
89 call test (a
,b
,c
) ! { dg-error "array without CONTIGUOUS" }
90 call test (a
,b(::2),c
) ! { dg-error "array without CONTIGUOUS" }
91 call test (a(::2),b
,c
) ! { dg-error "array without CONTIGUOUS" }
93 call test (a
,b
,f
%e
) ! { dg-error "array without CONTIGUOUS" }
94 call test (a
,f
%e
,c
) ! { dg-error "array without CONTIGUOUS" }
95 call test (f
%e
,b
,c
) ! { dg-error "array without CONTIGUOUS" }
96 call test (a
,b
,f
%e(::2)) ! { dg-error "array without CONTIGUOUS" }
97 call test (a
,f
%e(::2),c
) ! { dg-error "array without CONTIGUOUS" }
98 call test (f
%e(::2),b
,c
) ! { dg-error "array without CONTIGUOUS" }
107 subroutine test(u
, v
, w
)
108 integer, asynchronous
:: u(:), v(*)
109 integer, volatile :: w(:)
112 subroutine test2(x
,y
)
113 integer, asynchronous
:: x(:)
114 integer, volatile :: y(:)
116 subroutine test3(x
,y
)
117 integer, pointer, asynchronous
:: x(:)
118 integer, pointer, volatile :: y(:)
124 ! 12.5.2.7 Pointer dummy variables
125 ! C1241 The actual argument corresponding to a dummy pointer with the CONTIGUOUS attribute shall be
126 ! simply contiguous (6.5.4).
129 integer, pointer, contiguous
:: a(:)
130 integer, pointer :: b(:)
132 call test(b
) ! { dg-error "must be simply contiguous" }
135 integer, pointer, contiguous
:: x(:)
140 ! 12.5.2.8 Coarray dummy variables
141 ! If the dummy argument is an array coarray that has the CONTIGUOUS attribute or is not of assumed shape,
142 ! the corresponding actual argument shall be simply contiguous
144 subroutine sect12528(cob
)
145 integer, save :: coa(6)[*]
152 call test(cob
) ! { dg-error "must be simply contiguous" }
153 call test2(cob
) ! { dg-error "must be simply contiguous" }
157 integer, contiguous
:: x(:)[*]
165 end subroutine sect12528
171 integer, volatile,pointer :: a(:,:),i
172 call foo(a(2,2:3:2)) ! { dg-error "must be simply contiguous" }
175 integer, pointer, contiguous
, volatile :: x(:)
177 end subroutine test34