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