File: stmt-func01.f90

package info (click to toggle)
llvm-toolchain-20 1%3A20.1.8-1
  • links: PTS, VCS
  • area: main
  • in suites: experimental
  • size: 2,111,696 kB
  • sloc: cpp: 7,438,781; ansic: 1,393,871; asm: 1,012,926; python: 241,771; f90: 86,635; objc: 75,411; lisp: 42,144; pascal: 17,286; sh: 8,596; ml: 5,082; perl: 4,730; makefile: 3,591; awk: 3,523; javascript: 2,251; xml: 892; fortran: 672
file content (100 lines) | stat: -rw-r--r-- 3,195 bytes parent folder | download | duplicates (2)
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
! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
! C1577
program main
  type t1(k,l)
    integer, kind :: k = kind(1)
    integer, len :: l = 666
    integer(k) n
  end type t1
  interface
    pure integer function ifunc()
    end function
  end interface
  !PORTABILITY: Automatic data object 'x1' should not appear in the specification part of a main program
  type(t1(k=4,l=ifunc())) x1
  !PORTABILITY: Statement function 'sf1' should not contain an array constructor
  sf1(n) = sum([(j,j=1,n)])
  type(t1) sf2
  !PORTABILITY: Statement function 'sf2' should not contain a structure constructor
  sf2(n) = t1(n)
  !PORTABILITY: Statement function 'sf3' should not contain a type parameter inquiry
  sf3(n) = x1%l
  !ERROR: Recursive call to statement function 'sf4' is not allowed
  sf4(n) = sf4(n)
  !ERROR: Statement function 'sf5' may not reference another statement function 'sf6' that is defined later
  sf5(n) = sf6(n)
  real sf7
  !ERROR: Statement function 'sf6' may not reference another statement function 'sf7' that is defined later
  sf6(n) = sf7(n)
  !PORTABILITY: Statement function 'sf7' should not reference function 'explicit' that requires an explicit interface
  sf7(n) = explicit(n)
  real :: a(3) = [1., 2., 3.]
  !PORTABILITY: Statement function 'sf8' should not pass an array argument that is not a whole array
  sf8(n) = sum(a(1:2))
  sf8a(n) = sum(a) ! ok
  integer :: sf9
  !ERROR: Defining expression of statement function 'sf9' cannot be converted to its result type INTEGER(4)
  sf9(n) = "bad"
  !ERROR: Statement function 'sf10' may not reference another statement function 'sf11' that is defined later
  sf10(n) = sf11(n)
  sf11(n) = sf10(n) ! mutual recursion, caused crash
  integer(1) iarg1
  !PORTABILITY: nonstandard usage: based POINTER
  pointer(iarg1p, iarg1)
  sf13(iarg1) = iarg1
  ! executable part
  print *, sf13(iarg1) ! ok
  sf14 = 1.
 contains
  real function explicit(x,y)
    integer, intent(in) :: x
    integer, intent(in), optional :: y
    explicit = x
  end function
  pure function arr()
    real :: arr(2)
    arr = [1., 2.]
  end function
  subroutine foo
    !PORTABILITY: An implicitly typed statement function should not appear when the same symbol is available in its host scope
    sf14(x) = 2.*x
  end subroutine
end

subroutine s0
  allocatable :: sf
  !ERROR: 'sf' is not a callable procedure
  sf(x) = 1.
end

subroutine s1
  asynchronous :: sf
  !ERROR: An entity may not have the ASYNCHRONOUS attribute unless it is a variable
  sf(x) = 1.
end

subroutine s2
  pointer :: sf
  !ERROR: A statement function must not have the POINTER attribute
  sf(x) = 1.
end

subroutine s3
  save :: sf
  !ERROR: The entity 'sf' with an explicit SAVE attribute must be a variable, procedure pointer, or COMMON block
  sf(x) = 1.
end

subroutine s4
  volatile :: sf
  !ERROR: VOLATILE attribute may apply only to a variable
  sf(x) = 1.
end

subroutine s5
  !ERROR: Invalid specification expression: reference to impure function 'k'
  real x(k())
  !WARNING: Name 'k' from host scope should have a type declaration before its local statement function definition
  !ERROR: 'k' is already declared in this scoping unit
  k() = 0.0
end