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