[LoopReroll] Add an extra defensive check to avoid SCEV assertion.
[llvm-project.git] / flang / test / Semantics / assign02.f90
blob76faa6f76f2f130df3d2765b2d27b398f925dfd9
1 ! RUN: %S/test_errors.sh %s %t %flang_fc1
2 ! REQUIRES: shell
3 ! Pointer assignment constraints 10.2.2.2
5 module m1
6 type :: t(k)
7 integer, kind :: k
8 end type
9 type t2
10 sequence
11 real :: t2Field
12 end type
13 contains
15 ! C852
16 subroutine s0
17 !ERROR: 'p1' may not have both the POINTER and TARGET attributes
18 real, pointer :: p1, p3
19 allocatable :: p2
20 !ERROR: 'sin' may not have both the POINTER and INTRINSIC attributes
21 real, intrinsic, pointer :: sin
22 target :: p1
23 !ERROR: 'p2' may not have both the POINTER and ALLOCATABLE attributes
24 pointer :: p2
25 !ERROR: 'a' may not have the POINTER attribute because it is a coarray
26 real, pointer :: a(:)[*]
27 end
29 ! C1015
30 subroutine s1
31 real, target :: r
32 real(8), target :: r8
33 logical, target :: l
34 real, pointer :: p
35 p => r
36 !ERROR: Target type REAL(8) is not compatible with pointer type REAL(4)
37 p => r8
38 !ERROR: Target type LOGICAL(4) is not compatible with pointer type REAL(4)
39 p => l
40 end
42 ! C1019
43 subroutine s2
44 real, target :: r1(4), r2(4,4)
45 real, pointer :: p(:)
46 p => r1
47 !ERROR: Pointer has rank 1 but target has rank 2
48 p => r2
49 end
51 ! C1015
52 subroutine s3
53 type(t(1)), target :: x1
54 type(t(2)), target :: x2
55 type(t(1)), pointer :: p
56 p => x1
57 !ERROR: Target type t(k=2_4) is not compatible with pointer type t(k=1_4)
58 p => x2
59 end
61 ! C1016
62 subroutine s4(x)
63 class(*), target :: x
64 type(t(1)), pointer :: p1
65 type(t2), pointer :: p2
66 class(*), pointer :: p3
67 real, pointer :: p4
68 p2 => x ! OK - not extensible
69 p3 => x ! OK - unlimited polymorphic
70 !ERROR: Pointer type must be unlimited polymorphic or non-extensible derived type when target is unlimited polymorphic
71 p1 => x
72 !ERROR: Pointer type must be unlimited polymorphic or non-extensible derived type when target is unlimited polymorphic
73 p4 => x
74 end
76 ! C1020
77 subroutine s5
78 real, target :: x[*]
79 real, target, volatile :: y[*]
80 real, pointer :: p
81 real, pointer, volatile :: q
82 p => x
83 !ERROR: Pointer must be VOLATILE when target is a VOLATILE coarray
84 p => y
85 !ERROR: Pointer may not be VOLATILE when target is a non-VOLATILE coarray
86 q => x
87 q => y
88 end
90 ! C1021, C1023
91 subroutine s6
92 real, target :: x
93 real :: p
94 type :: tp
95 real, pointer :: a
96 real :: b
97 end type
98 type(tp) :: y
99 !ERROR: 'p' is not a pointer
100 p => x
101 y%a => x
102 !ERROR: 'b' is not a pointer
103 y%b => x
106 !C1025 (R1037) The expr shall be a designator that designates a
107 !variable with either the TARGET or POINTER attribute and is not
108 !an array section with a vector subscript, or it shall be a reference
109 !to a function that returns a data pointer.
110 subroutine s7
111 real, target :: a
112 real, pointer :: b
113 real, pointer :: c
114 real :: d
115 b => a
116 c => b
117 !ERROR: In assignment to object pointer 'b', the target 'd' is not an object with POINTER or TARGET attributes
118 b => d
121 ! C1025
122 subroutine s8
123 real :: a(10)
124 integer :: b(10)
125 real, pointer :: p(:)
126 !ERROR: An array section with a vector subscript may not be a pointer target
127 p => a(b)
130 ! C1025
131 subroutine s9
132 real, target :: x
133 real, pointer :: p
134 p => f1()
135 !ERROR: pointer 'p' is associated with the result of a reference to function 'f2' that is a not a pointer
136 p => f2()
137 contains
138 function f1()
139 real, pointer :: f1
140 f1 => x
142 function f2()
143 real :: f2
144 f2 = x
148 ! C1026 (R1037) A data-target shall not be a coindexed object.
149 subroutine s10
150 real, target :: a[*]
151 real, pointer :: b
152 !ERROR: A coindexed object may not be a pointer target
153 b => a[1]
158 module m2
159 type :: t1
160 real :: a
161 end type
162 type :: t2
163 type(t1) :: b
164 type(t1), pointer :: c
165 real :: d
166 end type
169 subroutine s2
170 use m2
171 real, pointer :: p
172 type(t2), target :: x
173 type(t2) :: y
174 !OK: x has TARGET attribute
175 p => x%b%a
176 !OK: c has POINTER attribute
177 p => y%c%a
178 !ERROR: In assignment to object pointer 'p', the target 'y%b%a' is not an object with POINTER or TARGET attributes
179 p => y%b%a
180 associate(z => x%b)
181 !OK: x has TARGET attribute
182 p => z%a
183 end associate
184 associate(z => y%c)
185 !OK: c has POINTER attribute
186 p => z%a
187 end associate
188 associate(z => y%b)
189 !ERROR: In assignment to object pointer 'p', the target 'z%a' is not an object with POINTER or TARGET attributes
190 p => z%a
191 end associate
192 associate(z => y%b%a)
193 !ERROR: In assignment to object pointer 'p', the target 'z' is not an object with POINTER or TARGET attributes
194 p => z
195 end associate