xref: /llvm-project/flang/test/Semantics/associate03.f90 (revision e73d51d3c8ea61fa34658f22147e65f95411eca2)
1! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
2! A construct entity does not have the POINTER or ALLOCATABLE attribute,
3! except in SELECT RANK.
4
5subroutine test(up,ua,rp,ra)
6  class(*), pointer :: up
7  class(*), allocatable :: ua
8  real, pointer :: rp(..)
9  real, allocatable :: ra(..)
10  real, target :: x
11  real, pointer :: p
12  real, allocatable :: a
13  associate (s => p)
14    !ERROR: The left-hand side of a pointer assignment is not definable
15    !BECAUSE: 's' is not a pointer
16    s => x
17    !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
18    allocate(s)
19    !ERROR: Name in DEALLOCATE statement must have the ALLOCATABLE or POINTER attribute
20    deallocate(s)
21    !ERROR: 's' may not appear in NULLIFY
22    !BECAUSE: 's' is not a pointer
23    nullify(s)
24  end associate
25  select type(s => up)
26  type is (real)
27    !ERROR: The left-hand side of a pointer assignment is not definable
28    !BECAUSE: 's' is not a pointer
29    s => x
30    !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
31    allocate(s)
32    !ERROR: Name in DEALLOCATE statement must have the ALLOCATABLE or POINTER attribute
33    deallocate(s)
34    !ERROR: 's' may not appear in NULLIFY
35    !BECAUSE: 's' is not a pointer
36    nullify(s)
37  end select
38  select rank(s => rp)
39  rank(0)
40    s => x ! ok
41    allocate(s) ! ok
42    deallocate(s) ! ok
43    nullify(s) ! ok
44  !ERROR: RANK (*) cannot be used when selector is POINTER or ALLOCATABLE
45  rank(*)
46  rank default
47    !ERROR: The left-hand side of a pointer assignment must not be an assumed-rank dummy argument
48    !ERROR: pointer 's' associated with object 'x' with incompatible type or shape
49    s => x
50    !ERROR: An assumed-rank dummy argument may not appear in an ALLOCATE statement
51    allocate(s)
52    deallocate(s) ! ok
53    nullify(s) ! ok
54  end select
55  associate (s => a)
56    !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
57    allocate(s)
58    !ERROR: Name in DEALLOCATE statement must have the ALLOCATABLE or POINTER attribute
59    deallocate(s)
60  end associate
61  select type(s => ua)
62  type is (real)
63    !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
64    allocate(s)
65    !ERROR: Name in DEALLOCATE statement must have the ALLOCATABLE or POINTER attribute
66    deallocate(s)
67  end select
68  select rank(s => ra)
69  rank(0)
70    allocate(s) ! ok
71    deallocate(s) ! ok
72  !ERROR: RANK (*) cannot be used when selector is POINTER or ALLOCATABLE
73  rank(*)
74  rank default
75    !ERROR: An assumed-rank dummy argument may not appear in an ALLOCATE statement
76    allocate(s)
77    deallocate(s) ! ok
78  end select
79end
80