File: resolve69.f90

package info (click to toggle)
llvm-toolchain-16 1%3A16.0.6-15~deb11u2
  • links: PTS, VCS
  • area: main
  • in suites: bullseye
  • size: 1,634,820 kB
  • sloc: cpp: 6,179,261; ansic: 1,216,205; asm: 741,319; python: 196,614; objc: 75,325; f90: 49,640; lisp: 32,396; pascal: 12,286; sh: 9,394; perl: 7,442; ml: 5,494; awk: 3,523; makefile: 2,723; javascript: 1,206; xml: 886; fortran: 581; cs: 573
file content (124 lines) | stat: -rw-r--r-- 5,435 bytes parent folder | download | duplicates (5)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
! RUN: %python %S/test_errors.py %s %flang_fc1
subroutine s1()
  ! C701 (R701) The type-param-value for a kind type parameter shall be a
  ! constant expression.
  !
  ! C702 (R701) A colon shall not be used as a type-param-value except in the
  ! declaration of an entity that has the POINTER or ALLOCATABLE attribute.
  !
  ! C704 (R703) In a declaration-type-spec, every type-param-value that is
  ! not a colon or an asterisk shall be a specification expression.
  !   Section 10.1.11 defines specification expressions
  !
  ! 15.4.2.2(4)(c) A procedure must have an explicit interface if it has a
  ! result that has a nonassumed type parameter value that is not a constant
  ! expression.
  !
  integer, parameter :: constVal = 1
  integer :: nonConstVal = 1
!ERROR: Invalid specification expression: reference to local entity 'nonconstval'
  character(nonConstVal) :: colonString1
  character(len=20, kind=constVal + 1) :: constKindString
  character(len=:, kind=constVal + 1), pointer :: constKindString1
!ERROR: 'constkindstring2' has a type CHARACTER(KIND=2,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
  character(len=:, kind=constVal + 1) :: constKindString2
!ERROR: Must be a constant value
  character(len=20, kind=nonConstVal) :: nonConstKindString
!ERROR: 'deferredstring' has a type CHARACTER(KIND=1,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
  character(len=:) :: deferredString
!ERROR: 'colonstring2' has a type CHARACTER(KIND=1,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
  character(:) :: colonString2
  !OK because of the allocatable attribute
  character(:), allocatable :: colonString3
!ERROR: 'foo1' has a type CHARACTER(KIND=1,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
  character(:), external :: foo1
!ERROR: 'foo2' has a type CHARACTER(KIND=1,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
  procedure(character(:)) :: foo2
  interface
    function foo3()
!ERROR: 'foo3' has a type CHARACTER(KIND=1,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
      character(:) foo3
    end function
  end interface

!ERROR: Must have INTEGER type, but is REAL(4)
  character(3.5) :: badParamValue

  type derived(typeKind, typeLen)
    integer, kind :: typeKind
    integer, len :: typeLen
    character(typeKind) :: kindValue
    character(typeLen) :: lenValue
  end type derived

  type (derived(constVal, 3)) :: constDerivedKind
!ERROR: Value of kind type parameter 'typekind' (nonconstval) must be a scalar INTEGER constant
!ERROR: Invalid specification expression: reference to local entity 'nonconstval'
  type (derived(nonConstVal, 3)) :: nonConstDerivedKind

  !OK because all type-params are constants
  type (derived(3, constVal)) :: constDerivedLen

!ERROR: Invalid specification expression: reference to local entity 'nonconstval'
  type (derived(3, nonConstVal)) :: nonConstDerivedLen
!ERROR: 'colonderivedlen' has a type derived(typekind=3_4,typelen=:) with a deferred type parameter but is neither an allocatable nor an object pointer
  type (derived(3, :)) :: colonDerivedLen
!ERROR: 'colonderivedlen1' has a type derived(typekind=:,typelen=:) with a deferred type parameter but is neither an allocatable nor an object pointer
  type (derived( :, :)) :: colonDerivedLen1
  type (derived( :, :)), pointer :: colonDerivedLen2
  type (derived(4, :)), pointer :: colonDerivedLen3
end subroutine s1

!C702
!ERROR: 'f1' has a type CHARACTER(KIND=1,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
character(:) function f1
end function

function f2
!ERROR: 'f2' has a type CHARACTER(KIND=1,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
  character(:) f2
end function

function f3() result(res)
!ERROR: 'res' has a type CHARACTER(KIND=1,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
  character(:) res
end function

!ERROR: 'f4' has a type CHARACTER(KIND=1,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
function f4
  implicit character(:)(f)
end function

!Not errors.

Program d5
  Type string(maxlen)
    Integer,Kind :: maxlen
    Character(maxlen) :: value
  End Type
  Type(string(80)) line
  line%value = 'ok'
  Print *,Trim(line%value)
End Program

subroutine outer
  integer n
 contains
  character(n) function inner1()
    inner1 = ''
  end function inner1
  function inner2()
    real inner2(n)
  end function inner2
end subroutine outer

subroutine s2(dp,dpp)
  !ERROR: 'dp' has a type CHARACTER(KIND=1,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
  procedure(character(:)) :: dp
  !ERROR: 'dpp' has a type CHARACTER(KIND=1,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
  procedure(character(:)), pointer :: dpp
  !ERROR: 'pp' has a type CHARACTER(KIND=1,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
  procedure(character(:)), pointer :: pp
  !ERROR: 'xp' has a type CHARACTER(KIND=1,LEN=:) with a deferred type parameter but is neither an allocatable nor an object pointer
  procedure(character(:)) :: xp
end subroutine