Remove check for Android in Mips.cpp (#123793)
[llvm-project.git] / flang / test / Semantics / undef-result01.f90
blobe1ae58dae7c0a693faaa2786c20a4fe56066cb14
1 ! RUN: %python %S/test_errors.py %s %flang_fc1 -Werror
3 !WARNING: Function result is never defined
4 function basic()
5 end
7 function defdByIntentOut()
8 call intentout(defdByIntentOut)
9 contains
10 subroutine intentout(x)
11 real, intent(out) :: x
12 end
13 end
15 function defdByIntentInOut()
16 call intentinout(defdByIntentInOut)
17 contains
18 subroutine intentInout(x)
19 real, intent(out) :: x
20 end
21 end
23 function defdByIntentInPtr()
24 real, target :: defdByIntentInPtr
25 call intentInPtr(defdByIntentInPtr)
26 contains
27 subroutine intentInPtr(p)
28 real, intent(in), pointer :: p
29 end
30 end
32 !WARNING: Function result is never defined
33 function notDefdByCall()
34 call intentin(notDefdByCall)
35 contains
36 subroutine intentin(n)
37 integer, intent(in) :: n
38 end
39 end
41 !WARNING: Function result is never defined
42 function basicAlloc()
43 real, allocatable :: basicAlloc
44 allocate(basicAlloc)
45 end
47 function allocPtr()
48 real, pointer :: allocPtr
49 allocate(allocPtr) ! good enough for pointer
50 end
52 function sourcedAlloc()
53 real, allocatable :: sourcedAlloc
54 allocate(sourcedAlloc, source=0.)
55 end
57 function defdByEntry()
58 entry entry1
59 entry1 = 0.
60 end
62 function defdByEntry2()
63 entry entry2() result(entryResult)
64 entryResult = 0.
65 end
67 function usedAsTarget()
68 real, target :: usedAsTarget
69 real, pointer :: p
70 p => usedAsTarget
71 end
73 function entryUsedAsTarget()
74 real, target :: entryResult
75 real, pointer :: p
76 entry entry5() result(entryResult)
77 p => entryResult
78 end
80 function defdByCall()
81 call implicitInterface(defdByCall)
82 end
84 function defdInInternal()
85 contains
86 subroutine internal
87 defdInInternal = 0.
88 end
89 end
91 function defdByEntryInInternal()
92 entry entry3() result(entryResult)
93 contains
94 subroutine internal
95 entryResult = 0.
96 end
97 end
99 type(defaultInitialized) function defdByDefault()
100 type defaultInitialized
101 integer :: n = 123
102 end type
105 integer function defdByDo()
106 do defdByDo = 1, 10
107 end do
110 function defdByRead()
111 read(*,*) defdByRead
112 end function
114 function defdByNamelist()
115 namelist /nml/ defdByNamelist
116 read(*,nml=nml)
119 character(4) function defdByWrite()
120 write(defdByWrite,*) 'abcd'
123 integer function defdBySize()
124 real arr(10)
125 read(*,size=defdBySize) arr
128 character(40) function defdByIomsg()
129 !WARNING: IOMSG= is useless without either ERR= or IOSTAT=
130 write(123,*,iomsg=defdByIomsg)
133 character(20) function defdByInquire()
134 inquire(6,status=defdByInquire)
137 !WARNING: Function result is never defined
138 character(20) function notDefdByInquire()
139 inquire(file=notDefdByInquire)
142 integer function defdByNewunit()
143 open(newunit=defdByNewunit, file="foo.txt")
146 function defdByAssociate()
147 associate(s => defdByAssociate)
148 s = 1.
149 end associate
152 function defdByElementArgToImplicit() result(r)
153 real r(1)
154 call define(r(1))