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