• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1! RUN: %S/test_errors.sh %s %t %f18
2! Check for semantic errors in ALLOCATE statements
3
4!TODO: mixing expr and source-expr?
5!TODO: using subcomponent in source expressions
6
7subroutine C939_C942a_C945b(xsrc1a, xsrc1c, xsrc0, xsrc2a, xsrc2c, pos)
8! C939: If an allocate-object is an array, either allocate-shape-spec-list shall
9! appear in its allocation, or source-expr shall appear in the ALLOCATE
10! statement and have the same rank as the allocate-object.
11  type A
12    real, pointer :: x(:)
13  end type
14  real, allocatable :: x0
15  real, allocatable :: x1(:)
16  real, pointer :: x2(:, :, :)
17  type(A) a1
18  type(A), allocatable :: a2(:, :)
19
20  real xsrc0
21  real xsrc1a(*)
22  real xsrc1b(2:7)
23  real, pointer :: xsrc1c(:)
24  real xsrc2a(4:8, 12, *)
25  real xsrc2b(2:7, 5, 9)
26  real, pointer :: xsrc2c(:, :, :)
27  integer pos
28
29  allocate(x1(5))
30  allocate(x1(2:7))
31  allocate(x1, SOURCE=xsrc1a(2:7))
32  allocate(x1, MOLD=xsrc1b)
33  allocate(x1, SOURCE=xsrc1c)
34
35  allocate(x2(2,3,4))
36  allocate(x2(2:7,3:8,4:9))
37  allocate(x2, SOURCE=xsrc2a(4:8, 1:12, 2:5))
38  allocate(x2, MOLD=cos(xsrc2b))
39  allocate(x2, SOURCE=xsrc2c)
40
41  allocate(x1(5), x2(2,3,4), a1%x(5), a2(1,2)%x(4))
42  allocate(x1, a1%x, a2(1,2)%x, SOURCE=xsrc1a(2:7))
43  allocate(x1, a1%x, a2(1,2)%x, MOLD=xsrc1b)
44  allocate(x1, a1%x, a2(1,2)%x, SOURCE=xsrc1c)
45
46  allocate(x0, x1(5), x2(2,3,4), a1%x(5), SOURCE=xsrc0)
47
48  ! There are NO requirements that mold expression rank match the
49  ! allocated-objects when allocate-shape-spec-lists are given.
50  ! If it is not needed, the shape of MOLD should be simply ignored.
51  allocate(x0, x1(5), x2(2,3,4), a1%x(5), MOLD=xsrc0)
52  allocate(x0, x1(5), x2(2,3,4), a1%x(5), MOLD=xsrc1b)
53  allocate(x0, x1(5), x2(2,3,4), a1%x(5), MOLD=xsrc2b)
54
55  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
56  allocate(x1)
57  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
58  allocate(x1, SOURCE=xsrc0)
59  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
60  allocate(x1, MOLD=xsrc2c)
61
62  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
63  allocate(x2, SOURCE=xsrc1a(2:7))
64  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
65  allocate(x2, MOLD=xsrc1b)
66  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
67  allocate(x2, SOURCE=xsrc1c)
68
69  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
70  allocate(a1%x)
71  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
72  allocate(a2(5,3)%x)
73  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
74  allocate(x1(5), x2(2,3,4), a1%x, a2(1,2)%x(4))
75  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
76  allocate(x2, a2(1,2)%x, SOURCE=xsrc2a(4:8, 1:12, 2:5))
77  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
78  allocate(a1%x, MOLD=xsrc0)
79
80 !C942a: The number of allocate-shape-specs in an allocate-shape-spec-list shall
81 !be the same as the rank of the allocate-object. [...] (co-array stuffs).
82
83 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
84 allocate(x1(5, 5))
85 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
86 allocate(x1(2:3, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 1, 2, 1, 2))
87 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
88 allocate(x2(pos))
89 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
90 allocate(x2(2, 3, pos+1, 5))
91 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
92 allocate(x1(5), x2(2,4), a1%x(5), a2(1,2)%x(4))
93
94 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
95 allocate(x1(2), a1%x(2,5), a2(1,2)%x(2))
96
97 ! Test the check is not influenced by SOURCE
98 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
99 allocate(a1%x(5, 4, 3), SOURCE=xsrc2a(1:5, 1:4, 1:3))
100 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
101 allocate(x2(5), MOLD=xsrc1a(1:5))
102 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
103 allocate(a1%x(5, 4, 3), MOLD=xsrc1b)
104 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
105 allocate(x2(5), SOURCE=xsrc2b)
106
107 ! C945b: If SOURCE= appears, source-expr shall be a scalar or have the same
108 ! rank as each allocate-object.
109 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
110 allocate(x0, SOURCE=xsrc1b)
111 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
112 allocate(x2(2, 5, 7), SOURCE=xsrc1a(2:7))
113 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
114 allocate(x2(2, 5, 7), SOURCE=xsrc1c)
115
116 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
117 allocate(x1(5), SOURCE=xsrc2a(4:8, 1:12, 2:5))
118 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
119 allocate(x1(3), SOURCE=cos(xsrc2b))
120 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
121 allocate(x1(100), SOURCE=xsrc2c)
122
123 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
124 allocate(a1%x(10), x2(20, 30, 40), a2(1,2)%x(50), SOURCE=xsrc1c)
125 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
126 allocate(a1%x(25), SOURCE=xsrc2b)
127
128end subroutine
129
130subroutine C940(a1, pos)
131! If allocate-object is scalar, allocate-shape-spec-list shall not appear.
132  type A
133    integer(kind=8), allocatable :: i
134  end type
135
136  type B(k, l1, l2, l3)
137    integer, kind :: k
138    integer, len :: l1, l2, l3
139    real(kind=k) x(-1:l1, 0:l2, 1:l3)
140  end type
141
142  integer pos
143  class(A), allocatable :: a1(:)
144  real, pointer :: x
145  type(B(8,4,5,6)), allocatable :: b1
146
147  ! Nominal
148  allocate(x)
149  allocate(a1(pos)%i)
150  allocate(b1)
151
152  !ERROR: Shape specifications must not appear when allocatable object is scalar
153  allocate(x(pos))
154  !ERROR: Shape specifications must not appear when allocatable object is scalar
155  allocate(a1(pos)%i(5:2))
156  !ERROR: Shape specifications must not appear when allocatable object is scalar
157  allocate(b1(1))
158end subroutine
159