xref: /llvm-project/flang/test/Semantics/spec-expr.f90 (revision 26ac30bcec71ae97ba740fb6cf473eac3ac37887)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2! Tests for the 14 items that specify a "specification expression" in section
3! 10.1.11
4
5! a constant or subobject of a constant,
6subroutine s1()
7  type dType
8    integer :: field
9  end type dType
10
11  type(dType), parameter :: dConst = dType(3)
12  real, dimension(3) :: realVar1
13  real, dimension(dConst%field) :: realVar2
14end subroutine s1
15
16! an object designator with a base object that is a dummy argument that has
17! neither the OPTIONAL nor the INTENT (OUT) attribute,
18subroutine s2(inArg, inoutArg, outArg, optArg)
19  integer, intent(in) :: inArg
20  integer, intent(inout) :: inoutArg
21  integer, intent(out) :: outArg
22  integer, intent(in), optional :: optArg
23  real, dimension(inArg) :: realVar1
24  real, dimension(inoutArg) :: realVar2
25  !ERROR: Invalid specification expression: reference to INTENT(OUT) dummy argument 'outarg'
26  real, dimension(outArg) :: realVar3
27  !ERROR: Invalid specification expression: reference to OPTIONAL dummy argument 'optarg'
28  real, dimension(optArg) :: realVar4
29
30  outArg = 3
31end subroutine s2
32
33! an object designator with a base object that is in a common block,
34subroutine s3()
35  integer :: intVar
36  common intCommonVar
37  real, dimension(intCommonVar) :: realVar
38end subroutine s3
39
40! an object designator with a base object that is made accessible by
41!    use or host association,
42module m4
43  integer :: intVar
44end module m4
45
46subroutine s4()
47  use m4
48  real, dimension(intVar) :: realVar
49end subroutine s4
50
51! an array constructor where each element and each scalar-int-expr of
52!   each ac-implied-do-control is a restricted expression,
53subroutine s5()
54  real, dimension(storage_size([1,2])) :: realVar
55end subroutine s5
56
57! a structure constructor where each component is a restricted expression,
58subroutine s6()
59  type :: dType
60    integer :: field1
61    integer :: field2
62  end type dType
63
64  real, dimension(storage_size(dType(1, 2))) :: realArray
65end subroutine s6
66
67! a specification inquiry where each designator or argument is
68!   (a) a restricted expression or
69subroutine s7a()
70  real, dimension(3) :: realArray1
71  real, dimension(size(realArray1)) :: realArray2
72end subroutine s7a
73
74! a specification inquiry where each designator or argument is
75!   (b) a variable that is not an optional dummy argument, and whose
76!     properties inquired about are not
77!     (i)   dependent on the upper bound of the last dimension of an
78!       assumed-size array,
79subroutine s7bi(assumedArg)
80  integer, dimension(2, *) :: assumedArg
81  real, dimension(ubound(assumedArg, 1)) :: realArray1
82  !ERROR: DIM=2 dimension is out of range for rank-2 assumed-size array
83  real, dimension(ubound(assumedArg, 2)) :: realArray2
84end subroutine s7bi
85
86! a specification inquiry where each designator or argument is
87!   (b) a variable that is not an optional dummy argument, and whose
88!     properties inquired about are not
89!     (ii)  deferred, or
90subroutine s7bii(dummy)
91  character(len=:), pointer :: dummy
92  ! Should be an error since "dummy" is deferred, but all compilers handle it
93  real, dimension(len(dummy)) :: realArray
94end subroutine s7bii
95
96! a specification inquiry where each designator or argument is
97!   (b) a variable that is not an optional dummy argument, and whose
98!     properties inquired about are not
99!  (iii) defined by an expression that is not a restricted expression,
100subroutine s7biii(x, y)
101  real, intent(out) :: x(:)
102  real, optional :: y(:)
103  integer, parameter :: localConst = 5
104  integer :: local = 5
105  ! OK, since "localConst" is a constant
106  real, dimension(localConst) :: realArray1
107  !PORTABILITY: specification expression refers to local object 'local' (initialized and saved)
108  real, dimension(local) :: realArray2
109  real, dimension(size(realArray1)) :: realArray3 ! ok
110  real, dimension(size(x)) :: realArray4 ! ok
111  real, dimension(merge(1,2,present(y))) :: realArray5 ! ok
112  !ERROR: Invalid specification expression: reference to OPTIONAL dummy argument 'y'
113  real, dimension(size(y)) :: realArray6
114end subroutine s7biii
115
116! a specification inquiry that is a constant expression,
117subroutine s8()
118  integer :: iVar
119  real, dimension(bit_size(iVar)) :: realArray
120end subroutine s8
121
122! a reference to the intrinsic function PRESENT,
123subroutine s9(optArg)
124  integer, optional :: optArg
125  real, dimension(merge(3, 4, present(optArg))) :: realArray
126end subroutine s9
127
128! a reference to any other standard intrinsic function where each
129!   argument is a restricted expression,
130subroutine s10()
131  integer :: iVar
132  real, dimension(bit_size(iVar)) :: realArray
133end subroutine s10
134
135! a reference to a transformational function from the intrinsic module
136!   IEEE_ARITHMETIC, IEEE_EXCEPTIONS, or ISO_C_BINDING, where each argument
137!   is a restricted expression,
138subroutine s11()
139  use ieee_exceptions
140  real, dimension(merge(3, 4, ieee_support_halting(ieee_invalid))) :: realArray
141end subroutine s11
142
143! a reference to a specification function where each argument is a
144!   restricted expression,
145module m12
146  contains
147    pure function specFunc(arg)
148      integer, intent(in) :: arg
149      integer :: specFunc
150      specFunc = 3 + arg
151    end function specFunc
152end module m12
153
154subroutine s12()
155  use m12
156  real, dimension(specFunc(2)) :: realArray
157end subroutine s12
158
159! a type parameter of the derived type being defined,
160subroutine s13()
161  type :: dtype(param)
162    integer, len :: param
163    real, dimension(param) :: realField
164  end type dtype
165end subroutine s13
166
167! an ac-do-variable within an array constructor where each
168!   scalar-int-expr of the corresponding ac-implied-do-control is a restricted
169!   expression, or
170subroutine s14()
171  real, dimension(5) :: realField = [(i, i = 1, 5)]
172end subroutine s14
173
174! a restricted expression enclosed in parentheses,where each subscript,
175!   section subscript, substring starting point, substring ending point, and
176!   type parameter value is a restricted expression
177subroutine s15()
178  type :: dtype(param)
179    integer, len :: param
180    real, dimension((param + 2)) :: realField
181  end type dtype
182end subroutine s15
183
184! Regression test: don't get confused by host association
185subroutine s16(n)
186  integer :: n
187 contains
188  subroutine inner(r)
189    real, dimension(n) :: r
190  end subroutine
191end subroutine s16
192