1! RUN: %S/test_errors.sh %s %t %flang_fc1
2! REQUIRES: shell
3subroutine s1()
4  ! C701 (R701) The type-param-value for a kind type parameter shall be a
5  ! constant expression.
6  !
7  ! C702 (R701) A colon shall not be used as a type-param-value except in the
8  ! declaration of an entity that has the POINTER or ALLOCATABLE attribute.
9  !
10  ! C704 (R703) In a declaration-type-spec, every type-param-value that is
11  ! not a colon or an asterisk shall be a specification expression.
12  !   Section 10.1.11 defines specification expressions
13  !
14  integer, parameter :: constVal = 1
15  integer :: nonConstVal = 1
16!ERROR: Invalid specification expression: reference to local entity 'nonconstval'
17  character(nonConstVal) :: colonString1
18  character(len=20, kind=constVal + 1) :: constKindString
19  character(len=:, kind=constVal + 1), pointer :: constKindString1
20!ERROR: The type parameter LEN cannot be deferred without the POINTER or ALLOCATABLE attribute
21  character(len=:, kind=constVal + 1) :: constKindString2
22!ERROR: Must be a constant value
23  character(len=20, kind=nonConstVal) :: nonConstKindString
24!ERROR: The type parameter LEN cannot be deferred without the POINTER or ALLOCATABLE attribute
25  character(len=:) :: deferredString
26!ERROR: The type parameter LEN cannot be deferred without the POINTER or ALLOCATABLE attribute
27  character(:) :: colonString2
28  !OK because of the allocatable attribute
29  character(:), allocatable :: colonString3
30
31!ERROR: Must have INTEGER type, but is REAL(4)
32  character(3.5) :: badParamValue
33
34  type derived(typeKind, typeLen)
35    integer, kind :: typeKind
36    integer, len :: typeLen
37    character(typeKind) :: kindValue
38    character(typeLen) :: lenValue
39  end type derived
40
41  type (derived(constVal, 3)) :: constDerivedKind
42!ERROR: Value of kind type parameter 'typekind' (nonconstval) must be a scalar INTEGER constant
43!ERROR: Invalid specification expression: reference to local entity 'nonconstval'
44  type (derived(nonConstVal, 3)) :: nonConstDerivedKind
45
46  !OK because all type-params are constants
47  type (derived(3, constVal)) :: constDerivedLen
48
49!ERROR: Invalid specification expression: reference to local entity 'nonconstval'
50  type (derived(3, nonConstVal)) :: nonConstDerivedLen
51!ERROR: The value of type parameter 'typelen' cannot be deferred without the POINTER or ALLOCATABLE attribute
52  type (derived(3, :)) :: colonDerivedLen
53!ERROR: The value of type parameter 'typekind' cannot be deferred without the POINTER or ALLOCATABLE attribute
54!ERROR: The value of type parameter 'typelen' cannot be deferred without the POINTER or ALLOCATABLE attribute
55  type (derived( :, :)) :: colonDerivedLen1
56  type (derived( :, :)), pointer :: colonDerivedLen2
57  type (derived(4, :)), pointer :: colonDerivedLen3
58end subroutine s1
59Program d5
60  Type string(maxlen)
61    Integer,Kind :: maxlen
62    Character(maxlen) :: value
63  End Type
64  Type(string(80)) line
65  line%value = 'ok'
66  Print *,Trim(line%value)
67End Program
68