xref: /llvm-project/flang/test/Lower/power-operator.f90 (revision 1e27425ada352b97773730999fb0f63fab99a89e)
1! RUN: bbc -emit-fir %s -o - | FileCheck %s --check-prefixes="CHECK,PRECISE"
2! RUN: bbc --math-runtime=precise -emit-fir %s -o - | FileCheck %s --check-prefixes="PRECISE"
3! RUN: bbc --force-mlir-complex -emit-fir %s -o - | FileCheck %s --check-prefixes="FAST"
4! RUN: %flang_fc1 -emit-fir %s -o - | FileCheck %s --check-prefixes="CHECK,PRECISE"
5! RUN: %flang_fc1 -fapprox-func -emit-fir %s -o - | FileCheck %s --check-prefixes="CHECK,FAST"
6! RUN: %flang_fc1 -emit-fir -mllvm --math-runtime=precise %s -o - | FileCheck %s --check-prefixes="PRECISE"
7! RUN: %flang_fc1 -emit-fir -mllvm --force-mlir-complex %s -o - | FileCheck %s --check-prefixes="FAST"
8
9! Test power operation lowering
10
11! CHECK-LABEL: pow_r4_i4
12subroutine pow_r4_i4(x, y, z)
13  real :: x, z
14  integer :: y
15  z = x ** y
16  ! CHECK: math.fpowi {{.*}} : f32, i32
17end subroutine
18
19! CHECK-LABEL: pow_r4_r4
20subroutine pow_r4_r4(x, y, z)
21  real :: x, z, y
22  z = x ** y
23  ! CHECK: math.powf %{{.*}}, %{{.*}} : f32
24end subroutine
25
26! CHECK-LABEL: pow_r4_i8
27subroutine pow_r4_i8(x, y, z)
28  real :: x, z
29  integer(8) :: y
30  z = x ** y
31  ! CHECK: math.fpowi {{.*}} : f32, i64
32end subroutine
33
34! CHECK-LABEL: pow_r8_i4
35subroutine pow_r8_i4(x, y, z)
36  real(8) :: x, z
37  integer :: y
38  z = x ** y
39  ! CHECK: math.fpowi {{.*}} : f64, i32
40end subroutine
41
42! CHECK-LABEL: pow_r8_i8
43subroutine pow_r8_i8(x, y, z)
44  real(8) :: x, z
45  integer(8) :: y
46  z = x ** y
47  ! CHECK: math.fpowi {{.*}} : f64, i64
48end subroutine
49
50! CHECK-LABEL: pow_r8_r8
51subroutine pow_r8_r8(x, y, z)
52  real(8) :: x, z, y
53  z = x ** y
54  ! CHECK: math.powf %{{.*}}, %{{.*}} : f64
55end subroutine
56
57! CHECK-LABEL: pow_r4_r8
58subroutine pow_r4_r8(x, y, z)
59  real(4) :: x
60  real(8) :: z, y
61  z = x ** y
62  ! CHECK: %{{.*}} = fir.convert %{{.*}} : (f32) -> f64
63  ! CHECK: math.powf %{{.*}}, %{{.*}} : f64
64end subroutine
65
66! CHECK-LABEL: pow_i1_i1
67subroutine pow_i1_i1(x, y, z)
68  integer(1) :: x, y, z
69  z = x ** y
70  ! CHECK: math.ipowi %{{.*}}, %{{.*}} : i8
71end subroutine
72
73! CHECK-LABEL: pow_i2_i2
74subroutine pow_i2_i2(x, y, z)
75  integer(2) :: x, y, z
76  z = x ** y
77  ! CHECK: math.ipowi %{{.*}}, %{{.*}} : i16
78end subroutine
79
80! CHECK-LABEL: pow_i4_i4
81subroutine pow_i4_i4(x, y, z)
82  integer(4) :: x, y, z
83  z = x ** y
84  ! CHECK: math.ipowi %{{.*}}, %{{.*}} : i32
85end subroutine
86
87! CHECK-LABEL: pow_i8_i8
88subroutine pow_i8_i8(x, y, z)
89  integer(8) :: x, y, z
90  z = x ** y
91  ! CHECK: math.ipowi %{{.*}}, %{{.*}} : i64
92end subroutine
93
94! CHECK-LABEL: pow_c4_i4
95subroutine pow_c4_i4(x, y, z)
96  complex :: x, z
97  integer :: y
98  z = x ** y
99  ! CHECK: call @_FortranAcpowi
100end subroutine
101
102! CHECK-LABEL: pow_c4_i8
103subroutine pow_c4_i8(x, y, z)
104  complex :: x, z
105  integer(8) :: y
106  z = x ** y
107  ! CHECK: call @_FortranAcpowk
108end subroutine
109
110! CHECK-LABEL: pow_c8_i4
111subroutine pow_c8_i4(x, y, z)
112  complex(8) :: x, z
113  integer :: y
114  z = x ** y
115  ! CHECK: call @_FortranAzpowi
116end subroutine
117
118! CHECK-LABEL: pow_c8_i8
119subroutine pow_c8_i8(x, y, z)
120  complex(8) :: x, z
121  integer(8) :: y
122  z = x ** y
123  ! CHECK: call @_FortranAzpowk
124end subroutine
125
126! CHECK-LABEL: pow_c4_c4
127subroutine pow_c4_c4(x, y, z)
128  complex :: x, y, z
129  z = x ** y
130  ! FAST: complex.pow %{{.*}}, %{{.*}} : complex<f32>
131  ! PRECISE: call @cpowf
132end subroutine
133
134! CHECK-LABEL: pow_c8_c8
135subroutine pow_c8_c8(x, y, z)
136  complex(8) :: x, y, z
137  z = x ** y
138  ! FAST: complex.pow %{{.*}}, %{{.*}} : complex<f64>
139  ! PRECISE: call @cpow
140end subroutine
141
142