xref: /llvm-project/flang/test/Lower/PowerPC/ppc-intrinsics.f90 (revision 0b3f9d8561226e3771db7f49dfb43d1301efc3c3)
1! RUN: %flang_fc1 -flang-experimental-hlfir -emit-llvm %s -o - | FileCheck --check-prefixes="LLVMIR" %s
2! REQUIRES: target=powerpc{{.*}}
3
4! CHECK-LABEL: fmadd_testr
5subroutine fmadd_testr(a, x, y)
6  real :: a, x, y, z
7  z = fmadd(a, x, y)
8! LLVMIR: call contract float @llvm.fma.f32(float %{{[0-9]}}, float %{{[0-9]}}, float %{{[0-9]}})
9end
10
11! CHECK-LABEL: fmadd_testd
12subroutine fmadd_testd(a, x, y)
13  real(8) :: a, x, y, z
14  z = fmadd(a, x, y)
15! LLVMIR: call contract double @llvm.fma.f64(double %{{[0-9]}}, double %{{[0-9]}}, double %{{[0-9]}})
16end
17
18! CHECK-LABEL: fnmadd_testr
19subroutine fnmadd_testr(a, x, y)
20  real :: a, x, y, z
21  z = fnmadd(a, x, y)
22! LLVMIR: call contract float @llvm.ppc.fnmadds(float %{{[0-9]}}, float %{{[0-9]}}, float %{{[0-9]}})
23end
24
25! CHECK-LABEL: fnmadd_testd
26subroutine fnmadd_testd(a, x, y)
27  real(8) :: a, x, y, z
28  z = fnmadd(a, x, y)
29! LLVMIR: call contract double @llvm.ppc.fnmadd(double %{{[0-9]}}, double %{{[0-9]}}, double %{{[0-9]}})
30end
31
32! CHECK-LABEL: fmsub_testr
33subroutine fmsub_testr(a, x, y)
34  real :: a, x, y, z
35  z = fmsub(a, x, y)
36! LLVMIR: call contract float @llvm.ppc.fmsubs(float %{{[0-9]}}, float %{{[0-9]}}, float %{{[0-9]}})
37end
38
39! CHECK-LABEL: fmsub_testd
40subroutine fmsub_testd(a, x, y)
41  real(8) :: a, x, y, z
42  z = fmsub(a, x, y)
43! LLVMIR: call contract double @llvm.ppc.fmsub(double %{{[0-9]}}, double %{{[0-9]}}, double %{{[0-9]}})
44end
45
46! CHECK-LABEL: fnmsub_testr
47subroutine fnmsub_testr(a, x, y)
48  real :: a, x, y, z
49  z = fnmsub(a, x, y)
50! LLVMIR: call contract float @llvm.ppc.fnmsub.f32(float %{{[0-9]}}, float %{{[0-9]}}, float %{{[0-9]}})
51end
52
53! CHECK-LABEL: fnmsub_testd
54subroutine fnmsub_testd(a, x, y)
55  real(8) :: a, x, y, z
56  z = fnmsub(a, x, y)
57! LLVMIR: call contract double @llvm.ppc.fnmsub.f64(double %{{[0-9]}}, double %{{[0-9]}}, double %{{[0-9]}})
58end
59
60! CHECK-LABEL: fctid_test
61subroutine fctid_test(x)
62  real(8) :: x, r
63  r = fctid(x)
64! LLVMIR: call contract double @llvm.ppc.fctid(double %{{[0-9]}})
65end
66
67! CHECK-LABEL: fctidz_test
68subroutine fctidz_test(x)
69  real(8) :: x, r
70  r = fctidz(x)
71! LLVMIR: call contract double @llvm.ppc.fctidz(double %{{[0-9]}})
72end
73
74! CHECK-LABEL: fctiw_test
75subroutine fctiw_test(x)
76  real(8) :: x, r
77  r = fctiw(x)
78! LLVMIR: call contract double @llvm.ppc.fctiw(double %{{[0-9]}})
79end
80
81! CHECK-LABEL: fctiwz_test
82subroutine fctiwz_test(x)
83  real(8) :: x, r
84  r = fctiwz(x)
85! LLVMIR: call contract double @llvm.ppc.fctiwz(double %{{[0-9]}})
86end
87
88! CHECK-LABEL: fctudz_test
89subroutine fctudz_test(x)
90  real(8) :: x, r
91  r = fctudz(x)
92! LLVMIR: call contract double @llvm.ppc.fctudz(double %{{[0-9]}})
93end
94
95! CHECK-LABEL: fctuwz_test
96subroutine fctuwz_test(x)
97  real(8) :: x, r
98  r = fctuwz(x)
99! LLVMIR: call contract double @llvm.ppc.fctuwz(double %{{[0-9]}})
100end
101
102! CHECK-LABEL: fcfi_test
103subroutine fcfi_test(i)
104  real(8) :: i, r
105  r = fcfi(i)
106! LLVMIR: call contract double @llvm.ppc.fcfid(double %{{[0-9]}})
107end
108
109! CHECK-LABEL: fcfid_test
110subroutine fcfid_test(i)
111  real(8) :: i, r
112  r = fcfid(i)
113! LLVMIR: call contract double @llvm.ppc.fcfid(double %{{[0-9]}})
114end
115
116! CHECK-LABEL: fcfud_test
117subroutine fcfud_test(i)
118  real(8) :: i, r
119  r = fcfud(i)
120! LLVMIR: call contract double @llvm.ppc.fcfud(double %{{[0-9]}})
121end
122
123! CHECK-LABEL: fnabs_testr(x)
124subroutine fnabs_testr(x)
125  real :: x, y
126  y = fnabs(x)
127! LLVMIR: call contract float @llvm.ppc.fnabss(float %{{[0-9]}})
128end
129
130! CHECK-LABEL: fnabs_testd(x)
131subroutine fnabs_testd(x)
132  real(8) :: x, y
133  y = fnabs(x)
134! LLVMIR: call contract double @llvm.ppc.fnabs(double %{{[0-9]}})
135end
136
137!CHECK-LABEL: fre_test(x)
138subroutine fre_test(x)
139  real(8) :: x, y
140  y = fre(x)
141! LLVMIR: call contract double @llvm.ppc.fre(double %{{[0-9]}})
142end
143
144!CHECK-LABEL: fres_test(x)
145subroutine fres_test(x)
146  real :: x, y
147  y = fres(x)
148! LLVMIR: call contract float @llvm.ppc.fres(float %{{[0-9]}})
149end
150
151!CHECK-LABEL: frsqrte_test(x)
152subroutine frsqrte_test(x)
153  real(8) :: x, y
154  y = frsqrte(x)
155! LLVMIR: call contract double @llvm.ppc.frsqrte(double %{{[0-9]}})
156end
157
158!CHECK-LABEL: frsqrtes_test(x)
159subroutine frsqrtes_test(x)
160  real :: x, y
161  y = frsqrtes(x)
162! LLVMIR: call contract float @llvm.ppc.frsqrtes(float %{{[0-9]}})
163end
164
165! CHECK-LABEL: mtfsf_test
166subroutine mtfsf_test(r)
167  real(8) :: r
168  call mtfsf(1, r)
169! LLVMIR: call void @llvm.ppc.mtfsf(i32 {{[0-9]}}, double %{{[0-9]}})
170end
171
172! CHECK-LABEL: mtfsfi_test
173subroutine mtfsfi_test()
174  call mtfsfi(1, 2)
175! LLVMIR: call void @llvm.ppc.mtfsfi(i32 {{[0-9]}}, i32 {{[0-9]}})
176end
177