1! RUN: %S/test_errors.sh %s %t %f18
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  ! Should be an error since 2 is the last dimension of an 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()
101  integer, parameter :: localConst = 5
102  integer :: local = 5
103  ! OK, since "localConst" is a constant
104  real, dimension(localConst) :: realArray1
105  !ERROR: Invalid specification expression: reference to local entity 'local'
106  real, dimension(local) :: realArray2
107end subroutine s7biii
108
109! a specification inquiry that is a constant expression,
110subroutine s8()
111  integer :: iVar
112  real, dimension(bit_size(iVar)) :: realArray
113end subroutine s8
114
115! a reference to the intrinsic function PRESENT,
116subroutine s9(optArg)
117  integer, optional :: optArg
118  real, dimension(merge(3, 4, present(optArg))) :: realArray
119end subroutine s9
120
121! a reference to any other standard intrinsic function where each
122!   argument is a restricted expression,
123subroutine s10()
124  integer :: iVar
125  real, dimension(bit_size(iVar)) :: realArray
126end subroutine s10
127
128! a reference to a transformational function from the intrinsic module
129!   IEEE_ARITHMETIC, IEEE_EXCEPTIONS, or ISO_C_BINDING, where each argument
130!   is a restricted expression,
131subroutine s11()
132  use ieee_exceptions
133  real, dimension(merge(3, 4, ieee_support_halting(ieee_invalid))) :: realArray
134end subroutine s11
135
136! a reference to a specification function where each argument is a
137!   restricted expression,
138module m12
139  contains
140    pure function specFunc(arg)
141      integer, intent(in) :: arg
142      integer :: specFunc
143      specFunc = 3 + arg
144    end function specFunc
145end module m12
146
147subroutine s12()
148  use m12
149  real, dimension(specFunc(2)) :: realArray
150end subroutine s12
151
152! a type parameter of the derived type being defined,
153subroutine s13()
154  type :: dtype(param)
155    integer, len :: param
156    real, dimension(param) :: realField
157  end type dtype
158end subroutine s13
159
160! an ac-do-variable within an array constructor where each
161!   scalar-int-expr of the corresponding ac-implied-do-control is a restricted
162!   expression, or
163subroutine s14()
164  real, dimension(5) :: realField = [(i, i = 1, 5)]
165end subroutine s14
166
167! a restricted expression enclosed in parentheses,where each subscript,
168!   section subscript, substring starting point, substring ending point, and
169!   type parameter value is a restricted expression
170subroutine s15()
171  type :: dtype(param)
172    integer, len :: param
173    real, dimension((param + 2)) :: realField
174  end type dtype
175end subroutine s15
176