[flang] Accept polymorphic component element in storage_size
[llvm-project.git] / flang / test / Lower / call-site-mangling.f90
blob9c9205374a60f707bf72dc7cb2f3d038df2d1433
1 ! RUN: bbc %s -o "-" -emit-fir | FileCheck %s
3 subroutine sub()
4 real :: x
5 ! CHECK: fir.call @_QPasubroutine()
6 call AsUbRoUtInE();
7 ! CHECK: fir.call @_QPfoo()
8 x = foo()
9 end subroutine
11 module testMod
12 contains
13 subroutine sub()
14 end subroutine
16 function foo()
17 end function
18 end module
20 subroutine sub1()
21 use testMod
22 real :: x
23 ! CHECK: fir.call @_QMtestmodPsub()
24 call Sub();
25 ! CHECK: fir.call @_QMtestmodPfoo()
26 x = foo()
27 end subroutine
29 subroutine sub2()
30 use testMod, localfoo => foo, localsub => sub
31 real :: x
32 ! CHECK: fir.call @_QMtestmodPsub()
33 call localsub();
34 ! CHECK: fir.call @_QMtestmodPfoo()
35 x = localfoo()
36 end subroutine
40 subroutine sub3()
41 real :: x
42 ! CHECK: fir.call @_QFsub3Psub()
43 call sub();
44 ! CHECK: fir.call @_QFsub3Pfoo()
45 x = foo()
46 contains
47 subroutine sub()
48 end subroutine
50 function foo()
51 end function
52 end subroutine
54 function foo1()
55 real :: bar1
56 ! CHECK: fir.call @_QPbar1()
57 foo1 = bar1()
58 end function
60 function foo2()
61 ! CHECK: fir.call @_QPbar2()
62 foo2 = bar2()
63 end function
65 function foo3()
66 interface
67 real function bar3()
68 end function
69 end interface
70 ! CHECK: fir.call @_QPbar3()
71 foo3 = bar3()
72 end function
74 function foo4()
75 external :: bar4
76 ! CHECK: fir.call @_QPbar4()
77 foo4 = bar4()
78 end function
80 module test_bindmodule
81 contains
82 ! CHECK: func @modulecproc()
83 ! CHECK: func @bind_modulecproc()
84 subroutine modulecproc() bind(c)
85 end subroutine
86 subroutine modulecproc_1() bind(c, name="bind_modulecproc")
87 end subroutine
88 end module
89 ! CHECK-LABEL: func @_QPtest_bindmodule_call() {
90 subroutine test_bindmodule_call
91 use test_bindmodule
92 interface
93 subroutine somecproc() bind(c)
94 end subroutine
95 subroutine somecproc_1() bind(c, name="bind_somecproc")
96 end subroutine
97 end interface
98 ! CHECK: fir.call @modulecproc()
99 ! CHECK: fir.call @bind_modulecproc()
100 ! CHECK: fir.call @somecproc()
101 ! CHECK: fir.call @bind_somecproc()
102 call modulecproc()
103 call modulecproc_1()
104 call somecproc()
105 call somecproc_1()
106 end subroutine
108 ! CHECK-LABEL: func @_QPtest_bind_interface() {
109 subroutine test_bind_interface()
110 interface
111 subroutine some_bindc_iface() bind(C, name="some_name_some_foo_does_not_inherit")
112 end subroutine
113 end interface
114 procedure(some_bindc_iface) :: foo5
115 ! CHECK: fir.call @foo5
116 call foo5()