summaryrefslogtreecommitdiff
path: root/flang/test/Semantics/assign03.f90
blob: a80ef1e102b2b99c84376c8a4385558070ddf409 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
! RUN: %python %S/test_errors.py %s %flang_fc1
! Pointer assignment constraints 10.2.2.2 (see also assign02.f90)

module m
  interface
    subroutine s(i)
      integer i
    end
  end interface
  type :: t
    procedure(s), pointer, nopass :: p
    real, pointer :: q
  end type
contains
  ! C1027
  subroutine s1
    type(t), allocatable :: a(:)
    type(t), allocatable :: b[:]
    a(1)%p => s
    !ERROR: The left-hand side of a pointer assignment is not definable
    !BECAUSE: Procedure pointer 'p' may not be a coindexed object
    b[1]%p => s
  end
  ! C1028
  subroutine s2
    type(t) :: a
    a%p => s
    !ERROR: In assignment to object pointer 'q', the target 's' is a procedure designator
    a%q => s
  end
  ! C1029
  subroutine s3
    type(t) :: a
    a%p => f()  ! OK: pointer-valued function
    !ERROR: Subroutine pointer 'p' may not be associated with function designator 'f'
    a%p => f
  contains
    function f()
      procedure(s), pointer :: f
      f => s
    end
  end

  ! C1030 and 10.2.2.4 - procedure names as target of procedure pointer
  subroutine s4(s_dummy)
    procedure(s) :: s_dummy
    procedure(s), pointer :: p, q
    procedure(), pointer :: r
    integer :: i
    external :: s_external
    p => s_dummy
    p => s_internal
    p => s_module
    q => p
    r => s_external
  contains
    subroutine s_internal(i)
      integer i
    end
  end
  subroutine s_module(i)
    integer i
  end

  ! 10.2.2.4(3)
  subroutine s5
    procedure(f_impure1), pointer :: p_impure
    procedure(f_pure1), pointer :: p_pure
    !ERROR: Procedure pointer 'p_elemental' may not be ELEMENTAL
    procedure(f_elemental1), pointer :: p_elemental
    procedure(s_impure1), pointer :: sp_impure
    procedure(s_pure1), pointer :: sp_pure
    !ERROR: Procedure pointer 'sp_elemental' may not be ELEMENTAL
    procedure(s_elemental1), pointer :: sp_elemental

    p_impure => f_impure1 ! OK, same characteristics
    p_impure => f_pure1 ! OK, target may be pure when pointer is not
    !ERROR: Procedure pointer 'p_impure' associated with incompatible procedure designator 'f_elemental1': incompatible procedure attributes: Elemental
    p_impure => f_elemental1
    !ERROR: Procedure pointer 'p_impure' associated with incompatible procedure designator 'f_impureelemental1': incompatible procedure attributes: Elemental
    p_impure => f_ImpureElemental1 ! OK, target may be elemental

    sp_impure => s_impure1 ! OK, same characteristics
    sp_impure => s_pure1 ! OK, target may be pure when pointer is not
    !ERROR: Procedure pointer 'sp_impure' associated with incompatible procedure designator 's_elemental1': incompatible procedure attributes: Elemental
    sp_impure => s_elemental1

    !ERROR: PURE procedure pointer 'p_pure' may not be associated with non-PURE procedure designator 'f_impure1'
    p_pure => f_impure1
    p_pure => f_pure1 ! OK, same characteristics
    !ERROR: Procedure pointer 'p_pure' associated with incompatible procedure designator 'f_elemental1': incompatible procedure attributes: Elemental
    p_pure => f_elemental1
    !ERROR: PURE procedure pointer 'p_pure' may not be associated with non-PURE procedure designator 'f_impureelemental1'
    p_pure => f_impureElemental1

    !ERROR: PURE procedure pointer 'sp_pure' may not be associated with non-PURE procedure designator 's_impure1'
    sp_pure => s_impure1
    sp_pure => s_pure1 ! OK, same characteristics
    !ERROR: Procedure pointer 'sp_pure' associated with incompatible procedure designator 's_elemental1': incompatible procedure attributes: Elemental
    sp_pure => s_elemental1 ! OK, target may be elemental when pointer is not

    !ERROR: Procedure pointer 'p_impure' associated with incompatible procedure designator 'f_impure2': incompatible dummy argument #1: incompatible dummy data object intents
    p_impure => f_impure2
    !ERROR: Function pointer 'p_pure' associated with incompatible function designator 'f_pure2': function results have distinct types: INTEGER(4) vs REAL(4)
    p_pure => f_pure2
    !ERROR: Function pointer 'p_pure' associated with incompatible function designator 'ccos': function results have distinct types: INTEGER(4) vs COMPLEX(4)
    p_pure => ccos
    !ERROR: Procedure pointer 'p_impure' associated with incompatible procedure designator 'f_elemental2': incompatible procedure attributes: Elemental
    p_impure => f_elemental2

    !ERROR: Procedure pointer 'sp_impure' associated with incompatible procedure designator 's_impure2': incompatible procedure attributes: BindC
    sp_impure => s_impure2
    !ERROR: Procedure pointer 'sp_impure' associated with incompatible procedure designator 's_pure2': incompatible dummy argument #1: incompatible dummy data object intents
    sp_impure => s_pure2
    !ERROR: Procedure pointer 'sp_pure' associated with incompatible procedure designator 's_elemental2': incompatible procedure attributes: Elemental
    sp_pure => s_elemental2

    !ERROR: Function pointer 'p_impure' may not be associated with subroutine designator 's_impure1'
    p_impure => s_impure1

    !ERROR: Subroutine pointer 'sp_impure' may not be associated with function designator 'f_impure1'
    sp_impure => f_impure1

  contains
    integer function f_impure1(n)
      real, intent(in) :: n
      f_impure = n
    end
    pure integer function f_pure1(n)
      real, intent(in) :: n
      f_pure = n
    end
    elemental integer function f_elemental1(n)
      real, intent(in) :: n
      f_elemental = n
    end
    impure elemental integer function f_impureElemental1(n)
      real, intent(in) :: n
      f_impureElemental = n
    end

    integer function f_impure2(n)
      real, intent(inout) :: n
      f_impure = n
    end
    pure real function f_pure2(n)
      real, intent(in) :: n
      f_pure = n
    end
    elemental integer function f_elemental2(n)
      real, value :: n
      f_elemental = n
    end

    subroutine s_impure1(n)
      integer, intent(inout) :: n
      n = n + 1
    end
    pure subroutine s_pure1(n)
      integer, intent(inout) :: n
      n = n + 1
    end
    elemental subroutine s_elemental1(n)
      integer, intent(inout) :: n
      n = n + 1
    end

    subroutine s_impure2(n) bind(c)
      integer, intent(inout) :: n
      n = n + 1
    end subroutine s_impure2
    pure subroutine s_pure2(n)
      integer, intent(out) :: n
      n = 1
    end subroutine s_pure2
    elemental subroutine s_elemental2(m,n)
      integer, intent(inout) :: m, n
      n = m + n
    end subroutine s_elemental2
  end

  ! 10.2.2.4(4)
  subroutine s6
    procedure(s), pointer :: p, q
    procedure(), pointer :: r
    external :: s_external
    p => s_external ! OK for a pointer with an explicit interface to be associated with a procedure with an implicit interface
    r => s_module ! OK for a pointer with implicit interface to be associated with a procedure with an explicit interface.  See 10.2.2.4 (3)
  end

  ! 10.2.2.4(5)
  subroutine s7
    procedure(real) :: f_external
    external :: s_external
    procedure(), pointer :: p_s
    procedure(real), pointer :: p_f
    p_f => f_external
    p_s => s_external
    !Ok: p_s has no interface
    p_s => f_external
    !Ok: s_external has no interface
    p_f => s_external
  end

  ! C1017: bounds-spec
  subroutine s8
    real, target :: x(10, 10)
    real, pointer :: p(:, :)
    p(2:,3:) => x
    !ERROR: Pointer 'p' has rank 2 but the number of bounds specified is 1
    p(2:) => x
  end

  ! bounds-remapping
  subroutine s9
    real, target :: x(10, 10), y(100)
    real, pointer :: p(:, :)
    ! C1018
    !ERROR: Pointer 'p' has rank 2 but the number of bounds specified is 1
    p(1:100) => x
    ! 10.2.2.3(9)
    !ERROR: Pointer bounds remapping target must have rank 1 or be simply contiguous
    p(1:5,1:5) => x(1:10,::2)
    ! 10.2.2.3(9)
    !ERROR: Pointer bounds require 25 elements but target has only 20
    p(1:5,1:5) => x(:,1:2)
    !OK - rhs has rank 1 and enough elements
    p(1:5,1:5) => y(1:100:2)
    !OK - same, but from function result
    p(1:5,1:5) => f()
   contains
    function f()
      real, pointer :: f(:)
      f => y
    end function
  end

  subroutine s10
    integer, pointer :: p(:)
    type :: t
      integer :: a(4, 4)
      integer :: b
    end type
    type(t), target :: x
    type(t), target :: y(10,10)
    integer :: v(10)
    p(1:16) => x%a
    p(1:8) => x%a(:,3:4)
    p(1:1) => x%b  ! We treat scalars as simply contiguous
    p(1:1) => x%a(1,1)
    p(1:1) => y(1,1)%a(1,1)
    p(1:1) => y(:,1)%a(1,1)  ! Rank 1 RHS
    !ERROR: Pointer bounds remapping target must have rank 1 or be simply contiguous
    p(1:4) => x%a(::2,::2)
    !ERROR: Pointer bounds remapping target must have rank 1 or be simply contiguous
    p(1:100) => y(:,:)%b
    !ERROR: Pointer bounds remapping target must have rank 1 or be simply contiguous
    p(1:100) => y(:,:)%a(1,1)
    !ERROR: Pointer bounds remapping target must have rank 1 or be simply contiguous
    !ERROR: An array section with a vector subscript may not be a pointer target
    p(1:4) => x%a(:,v)
  end

  subroutine s11
    complex, target :: x(10,10)
    complex, pointer :: p(:)
    real, pointer :: q(:)
    p(1:100) => x(:,:)
    q(1:10) => x(1,:)%im
    !ERROR: Pointer bounds remapping target must have rank 1 or be simply contiguous
    q(1:100) => x(:,:)%re
  end

  ! Check is_contiguous, which is usually the same as when pointer bounds
  ! remapping is used.
  subroutine s12
    integer, pointer :: p(:)
    integer, pointer, contiguous :: pc(:)
    type :: t
      integer :: a(4, 4)
      integer :: b
    end type
    type(t), target :: x
    type(t), target :: y(10,10)
    integer :: v(10)
    logical(kind=merge(1,-1,is_contiguous(x%a(:,:)))) :: l1 ! known true
    logical(kind=merge(1,-1,is_contiguous(y(1,1)%a(1,1)))) :: l2 ! known true
    !ERROR: Must be a constant value
    logical(kind=merge(-1,-2,is_contiguous(y(:,1)%a(1,1)))) :: l3 ! unknown
    !ERROR: Must be a constant value
    logical(kind=merge(-1,-2,is_contiguous(y(:,1)%a(1,1)))) :: l4 ! unknown
    logical(kind=merge(-1,1,is_contiguous(x%a(:,v)))) :: l5 ! known false
    !ERROR: Must be a constant value
    logical(kind=merge(-1,-2,is_contiguous(y(v,1)%a(1,1)))) :: l6 ! unknown
    !ERROR: Must be a constant value
    logical(kind=merge(-1,-2,is_contiguous(p(:)))) :: l7 ! unknown
    logical(kind=merge(1,-1,is_contiguous(pc(:)))) :: l8 ! known true
    logical(kind=merge(-1,1,is_contiguous(pc(1:10:2)))) :: l9 ! known false
    logical(kind=merge(-1,1,is_contiguous(pc(10:1:-1)))) :: l10 ! known false
    logical(kind=merge(1,-1,is_contiguous(pc(1:10:1)))) :: l11 ! known true
    logical(kind=merge(-1,1,is_contiguous(pc(10:1:-1)))) :: l12 ! known false
    !ERROR: Must be a constant value
    logical(kind=merge(-1,1,is_contiguous(pc(::-1)))) :: l13 ! unknown (could be empty)
    logical(kind=merge(1,-1,is_contiguous(y(1,1)%a(::-1,1)))) :: l14 ! known true (empty)
    logical(kind=merge(1,-1,is_contiguous(y(1,1)%a(1,::-1)))) :: l15 ! known true (empty)
  end
  subroutine test3(b)
    integer, intent(inout) :: b(..)
    !ERROR: Must be a constant value
    integer, parameter :: i = rank(b)
  end subroutine

  subroutine s13
    external :: s_external
    procedure(), pointer :: ptr
    !Ok - don't emit an error about incompatible Subroutine attribute
    ptr => s_external
    call ptr
  end subroutine

  subroutine s14
    procedure(real), pointer :: ptr
    sf(x) = x + 1.
    !ERROR: Statement function 'sf' may not be the target of a pointer assignment
    ptr => sf
  end subroutine
end