File: undef-result01.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 (155 lines) | stat: -rw-r--r-- 2,831 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
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
! RUN: %python %S/test_errors.py %s %flang_fc1 -Werror

!WARNING: Function result is never defined
function basic()
end

function defdByIntentOut()
  call intentout(defdByIntentOut)
 contains
  subroutine intentout(x)
    real, intent(out) :: x
  end
end

function defdByIntentInOut()
  call intentinout(defdByIntentInOut)
 contains
  subroutine intentInout(x)
    real, intent(out) :: x
  end
end

function defdByIntentInPtr()
  real, target :: defdByIntentInPtr
  call intentInPtr(defdByIntentInPtr)
 contains
  subroutine intentInPtr(p)
    real, intent(in), pointer :: p
  end
end

!WARNING: Function result is never defined
function notDefdByCall()
  call intentin(notDefdByCall)
 contains
  subroutine intentin(n)
    integer, intent(in) :: n
  end
end

!WARNING: Function result is never defined
function basicAlloc()
  real, allocatable :: basicAlloc
  allocate(basicAlloc)
end

function allocPtr()
  real, pointer :: allocPtr
  allocate(allocPtr) ! good enough for pointer
end

function sourcedAlloc()
  real, allocatable :: sourcedAlloc
  allocate(sourcedAlloc, source=0.)
end

function defdByEntry()
  entry entry1
  entry1 = 0.
end

function defdByEntry2()
  entry entry2() result(entryResult)
  entryResult = 0.
end

function usedAsTarget()
  real, target :: usedAsTarget
  real, pointer :: p
  p => usedAsTarget
end

function entryUsedAsTarget()
  real, target :: entryResult
  real, pointer :: p
  entry entry5() result(entryResult)
  p => entryResult
end

function defdByCall()
  call implicitInterface(defdByCall)
end

function defdInInternal()
 contains
  subroutine internal
    defdInInternal = 0.
  end
end

function defdByEntryInInternal()
  entry entry3() result(entryResult)
 contains
  subroutine internal
    entryResult = 0.
  end
end

type(defaultInitialized) function defdByDefault()
  type defaultInitialized
    integer :: n = 123
  end type
end

integer function defdByDo()
  do defdByDo = 1, 10
  end do
end

function defdByRead()
  read(*,*) defdByRead
end function

function defdByNamelist()
  namelist /nml/ defdByNamelist
  read(*,nml=nml)
end

character(4) function defdByWrite()
  write(defdByWrite,*) 'abcd'
end

integer function defdBySize()
  real arr(10)
  read(*,size=defdBySize) arr
end

character(40) function defdByIomsg()
  !WARNING: IOMSG= is useless without either ERR= or IOSTAT=
  write(123,*,iomsg=defdByIomsg)
end

character(20) function defdByInquire()
  inquire(6,status=defdByInquire)
end

!WARNING: Function result is never defined
character(20) function notDefdByInquire()
  inquire(file=notDefdByInquire)
end

integer function defdByNewunit()
  open(newunit=defdByNewunit, file="foo.txt")
end

function defdByAssociate()
  associate(s => defdByAssociate)
    s = 1.
  end associate
end

function defdByElementArgToImplicit() result(r)
  real r(1)
  call define(r(1))
end