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