1! RUN: %S/test_errors.sh %s %t %flang_fc1
2! REQUIRES: shell
3! C701 The type-param-value for a kind type parameter shall be a constant
4! expression.  This constraint looks like a mistake in the standard.
5integer, parameter :: k = 8
6real, parameter :: l = 8.0
7integer :: n = 2
8!ERROR: Must be a constant value
9parameter(m=n)
10integer(k) :: x
11! C713 A scalar-int-constant-name shall be a named constant of type integer.
12!ERROR: Must have INTEGER type, but is REAL(4)
13integer(l) :: y
14!ERROR: Must be a constant value
15integer(n) :: z
16type t(k)
17  integer, kind :: k
18end type
19!ERROR: Type parameter 'k' lacks a value and has no default
20type(t( &
21!ERROR: Must have INTEGER type, but is LOGICAL(4)
22  .true.)) :: w
23!ERROR: Must have INTEGER type, but is REAL(4)
24real :: u(l*2)
25!ERROR: Must have INTEGER type, but is REAL(4)
26character(len=l) :: v
27!ERROR: Value of named constant 'o' (o) cannot be computed as a constant value
28real, parameter ::  o = o
29!ERROR: Must be a constant value
30integer, parameter ::  p = 0/0
31!ERROR: Must be a constant value
32integer, parameter ::  q = 1+2*(1/0)
33integer not_constant
34!ERROR: Must be a constant value
35integer, parameter :: s1 = not_constant/2
36!ERROR: Must be a constant value
37integer, parameter :: s2 = 3/not_constant
38!ERROR: Must be a constant value
39integer(kind=2/0) r
40integer, parameter :: sok(*)=[1,2]/[1,2]
41!ERROR: Must be a constant value
42integer, parameter :: snok(*)=[1,2]/[1,0]
43end
44