File: resolve09.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 (162 lines) | stat: -rw-r--r-- 3,220 bytes parent folder | download | duplicates (10)
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
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
! RUN: %python %S/test_errors.py %s %flang_fc1
integer :: y
procedure() :: a
procedure(real) :: b
call a  ! OK - can be function or subroutine
!ERROR: Cannot call subroutine 'a' like a function
c = a()
!ERROR: Cannot call function 'b' like a subroutine
call b
!ERROR: Cannot call function 'y' like a subroutine
call y
call x
!ERROR: Cannot call subroutine 'x' like a function
z = x()
end

subroutine s
  !ERROR: Cannot call function 'f' like a subroutine
  call f
  !ERROR: Cannot call subroutine 's' like a function
  i = s()
contains
  function f()
  end
end

subroutine s2
  ! subroutine vs. function is determined by use
  external :: a, b
  call a()
  !ERROR: Cannot call subroutine 'a' like a function
  x = a()
  x = b()
  !ERROR: Cannot call function 'b' like a subroutine
  call b()
end

subroutine s3
  ! subroutine vs. function is determined by use, even in internal subprograms
  external :: a
  procedure() :: b
contains
  subroutine s3a()
    x = a()
    call b()
  end
  subroutine s3b()
    !ERROR: Cannot call function 'a' like a subroutine
    call a()
    !ERROR: Cannot call subroutine 'b' like a function
    x = b()
  end
end

module m1
  !Function vs subroutine in a module is resolved to a subroutine if
  !no other information.
  external :: exts, extf, extunk
  procedure() :: procs, procf, procunk
contains
  subroutine s
    call exts()
    call procs()
    x = extf()
    x = procf()
  end
end

module m2
  use m1
 contains
  subroutine test
    call exts() ! ok
    call procs() ! ok
    call extunk() ! ok
    call procunk() ! ok
    x = extf() ! ok
    x = procf() ! ok
    !ERROR: Cannot call subroutine 'extunk' like a function
    !ERROR: Function result characteristics are not known
    x = extunk()
    !ERROR: Cannot call subroutine 'procunk' like a function
    !ERROR: Function result characteristics are not known
    x = procunk()
  end
end

module modulename
end

! Call to entity in global scope, even with IMPORT, NONE
subroutine s4
  block
    import, none
    integer :: i
    !ERROR: 'modulename' is not a callable procedure
    call modulename()
  end block
end

! Call to entity in global scope, even with IMPORT, NONE
subroutine s5
  block
    import, none
    integer :: i
    i = foo()
    !ERROR: Cannot call function 'foo' like a subroutine
    call foo()
  end block
end

subroutine s6
  call a6()
end
!ERROR: 'a6' was previously called as a subroutine
function a6()
  a6 = 0.0
end

subroutine s7
  x = a7()
end
!ERROR: 'a7' was previously called as a function
subroutine a7()
end

!OK: use of a8 and b8 is consistent
subroutine s8
  call a8()
  x = b8()
end
subroutine a8()
end
function b8()
  b8 = 0.0
end

subroutine s9
  type t
    procedure(), nopass, pointer :: p1, p2
  end type
  type(t) x
  print *, x%p1()
  call x%p2
  !ERROR: Cannot call function 'p1' like a subroutine
  call x%p1
  !ERROR: Cannot call subroutine 'p2' like a function
  print *, x%p2()
end subroutine

subroutine s10
  call a10
  !ERROR: Actual argument for 'a=' may not be a procedure
  print *, abs(a10)
end

subroutine s11
  real, pointer :: p(:)
  !ERROR: A NULL() pointer is not allowed for 'a=' intrinsic argument
  print *, rank(null())
  print *, rank(null(mold=p)) ! ok
end