[DebugInfo][RemoveDIs] Emulate inserting insts in dbg.value sequences (#73350)
[llvm-project.git] / flang / test / Lower / complex-operations.f90
blob2a353216978f0b184be375fa5ff961d7cd303c8f
1 ! RUN: bbc -hlfir=false %s -o - | FileCheck %s
3 ! CHECK-LABEL: @_QPadd_test
4 subroutine add_test(a,b,c)
5 complex :: a, b, c
6 ! CHECK-NOT: fir.extract_value
7 ! CHECK-NOT: fir.insert_value
8 ! CHECK: fir.addc {{.*}}: !fir.complex
9 a = b + c
10 end subroutine add_test
12 ! CHECK-LABEL: @_QPsub_test
13 subroutine sub_test(a,b,c)
14 complex :: a, b, c
15 ! CHECK-NOT: fir.extract_value
16 ! CHECK-NOT: fir.insert_value
17 ! CHECK: fir.subc {{.*}}: !fir.complex
18 a = b - c
19 end subroutine sub_test
21 ! CHECK-LABEL: @_QPmul_test
22 subroutine mul_test(a,b,c)
23 complex :: a, b, c
24 ! CHECK-NOT: fir.extract_value
25 ! CHECK-NOT: fir.insert_value
26 ! CHECK: fir.mulc {{.*}}: !fir.complex
27 a = b * c
28 end subroutine mul_test
30 ! CHECK-LABEL: @_QPdiv_test_half
31 ! CHECK-SAME: %[[AREF:.*]]: !fir.ref<!fir.complex<2>> {{.*}}, %[[BREF:.*]]: !fir.ref<!fir.complex<2>> {{.*}}, %[[CREF:.*]]: !fir.ref<!fir.complex<2>> {{.*}})
32 ! CHECK: %[[BVAL:.*]] = fir.load %[[BREF]] : !fir.ref<!fir.complex<2>>
33 ! CHECK: %[[CVAL:.*]] = fir.load %[[CREF]] : !fir.ref<!fir.complex<2>>
34 ! CHECK: %[[BVAL_CVT:.*]] = fir.convert %[[BVAL]] : (!fir.complex<2>) -> complex<f16>
35 ! CHECK: %[[CVAL_CVT:.*]] = fir.convert %[[CVAL]] : (!fir.complex<2>) -> complex<f16>
36 ! CHECK: %[[AVAL_CVT:.*]] = complex.div %[[BVAL_CVT]], %[[CVAL_CVT]] fastmath<contract> : complex<f16>
37 ! CHECK: %[[AVAL:.*]] = fir.convert %[[AVAL_CVT]] : (complex<f16>) -> !fir.complex<2>
38 ! CHECK: fir.store %[[AVAL]] to %[[AREF]] : !fir.ref<!fir.complex<2>>
39 subroutine div_test_half(a,b,c)
40 complex(kind=2) :: a, b, c
41 a = b / c
42 end subroutine div_test_half
44 ! CHECK-LABEL: @_QPdiv_test_bfloat
45 ! CHECK-SAME: %[[AREF:.*]]: !fir.ref<!fir.complex<3>> {{.*}}, %[[BREF:.*]]: !fir.ref<!fir.complex<3>> {{.*}}, %[[CREF:.*]]: !fir.ref<!fir.complex<3>> {{.*}})
46 ! CHECK: %[[BVAL:.*]] = fir.load %[[BREF]] : !fir.ref<!fir.complex<3>>
47 ! CHECK: %[[CVAL:.*]] = fir.load %[[CREF]] : !fir.ref<!fir.complex<3>>
48 ! CHECK: %[[BVAL_CVT:.*]] = fir.convert %[[BVAL]] : (!fir.complex<3>) -> complex<bf16>
49 ! CHECK: %[[CVAL_CVT:.*]] = fir.convert %[[CVAL]] : (!fir.complex<3>) -> complex<bf16>
50 ! CHECK: %[[AVAL_CVT:.*]] = complex.div %[[BVAL_CVT]], %[[CVAL_CVT]] fastmath<contract> : complex<bf16>
51 ! CHECK: %[[AVAL:.*]] = fir.convert %[[AVAL_CVT]] : (complex<bf16>) -> !fir.complex<3>
52 ! CHECK: fir.store %[[AVAL]] to %[[AREF]] : !fir.ref<!fir.complex<3>>
53 subroutine div_test_bfloat(a,b,c)
54 complex(kind=3) :: a, b, c
55 a = b / c
56 end subroutine div_test_bfloat
58 ! CHECK-LABEL: @_QPdiv_test_single
59 ! CHECK-SAME: %[[AREF:.*]]: !fir.ref<!fir.complex<4>> {{.*}}, %[[BREF:.*]]: !fir.ref<!fir.complex<4>> {{.*}}, %[[CREF:.*]]: !fir.ref<!fir.complex<4>> {{.*}})
60 ! CHECK: %[[BVAL:.*]] = fir.load %[[BREF]] : !fir.ref<!fir.complex<4>>
61 ! CHECK: %[[CVAL:.*]] = fir.load %[[CREF]] : !fir.ref<!fir.complex<4>>
62 ! CHECK: %[[BREAL:.*]] = fir.extract_value %[[BVAL]], [0 : index] : (!fir.complex<4>) -> f32
63 ! CHECK: %[[BIMAG:.*]] = fir.extract_value %[[BVAL]], [1 : index] : (!fir.complex<4>) -> f32
64 ! CHECK: %[[CREAL:.*]] = fir.extract_value %[[CVAL]], [0 : index] : (!fir.complex<4>) -> f32
65 ! CHECK: %[[CIMAG:.*]] = fir.extract_value %[[CVAL]], [1 : index] : (!fir.complex<4>) -> f32
66 ! CHECK: %[[AVAL:.*]] = fir.call @__divsc3(%[[BREAL]], %[[BIMAG]], %[[CREAL]], %[[CIMAG]]) fastmath<contract> : (f32, f32, f32, f32) -> !fir.complex<4>
67 ! CHECK: fir.store %[[AVAL]] to %[[AREF]] : !fir.ref<!fir.complex<4>>
68 subroutine div_test_single(a,b,c)
69 complex(kind=4) :: a, b, c
70 a = b / c
71 end subroutine div_test_single
73 ! CHECK-LABEL: @_QPdiv_test_double
74 ! CHECK-SAME: %[[AREF:.*]]: !fir.ref<!fir.complex<8>> {{.*}}, %[[BREF:.*]]: !fir.ref<!fir.complex<8>> {{.*}}, %[[CREF:.*]]: !fir.ref<!fir.complex<8>> {{.*}})
75 ! CHECK: %[[BVAL:.*]] = fir.load %[[BREF]] : !fir.ref<!fir.complex<8>>
76 ! CHECK: %[[CVAL:.*]] = fir.load %[[CREF]] : !fir.ref<!fir.complex<8>>
77 ! CHECK: %[[BREAL:.*]] = fir.extract_value %[[BVAL]], [0 : index] : (!fir.complex<8>) -> f64
78 ! CHECK: %[[BIMAG:.*]] = fir.extract_value %[[BVAL]], [1 : index] : (!fir.complex<8>) -> f64
79 ! CHECK: %[[CREAL:.*]] = fir.extract_value %[[CVAL]], [0 : index] : (!fir.complex<8>) -> f64
80 ! CHECK: %[[CIMAG:.*]] = fir.extract_value %[[CVAL]], [1 : index] : (!fir.complex<8>) -> f64
81 ! CHECK: %[[AVAL:.*]] = fir.call @__divdc3(%[[BREAL]], %[[BIMAG]], %[[CREAL]], %[[CIMAG]]) fastmath<contract> : (f64, f64, f64, f64) -> !fir.complex<8>
82 ! CHECK: fir.store %[[AVAL]] to %[[AREF]] : !fir.ref<!fir.complex<8>>
83 subroutine div_test_double(a,b,c)
84 complex(kind=8) :: a, b, c
85 a = b / c
86 end subroutine div_test_double
88 ! CHECK-LABEL: @_QPdiv_test_extended
89 ! CHECK-SAME: %[[AREF:.*]]: !fir.ref<!fir.complex<10>> {{.*}}, %[[BREF:.*]]: !fir.ref<!fir.complex<10>> {{.*}}, %[[CREF:.*]]: !fir.ref<!fir.complex<10>> {{.*}})
90 ! CHECK: %[[BVAL:.*]] = fir.load %[[BREF]] : !fir.ref<!fir.complex<10>>
91 ! CHECK: %[[CVAL:.*]] = fir.load %[[CREF]] : !fir.ref<!fir.complex<10>>
92 ! CHECK: %[[BREAL:.*]] = fir.extract_value %[[BVAL]], [0 : index] : (!fir.complex<10>) -> f80
93 ! CHECK: %[[BIMAG:.*]] = fir.extract_value %[[BVAL]], [1 : index] : (!fir.complex<10>) -> f80
94 ! CHECK: %[[CREAL:.*]] = fir.extract_value %[[CVAL]], [0 : index] : (!fir.complex<10>) -> f80
95 ! CHECK: %[[CIMAG:.*]] = fir.extract_value %[[CVAL]], [1 : index] : (!fir.complex<10>) -> f80
96 ! CHECK: %[[AVAL:.*]] = fir.call @__divxc3(%[[BREAL]], %[[BIMAG]], %[[CREAL]], %[[CIMAG]]) fastmath<contract> : (f80, f80, f80, f80) -> !fir.complex<10>
97 ! CHECK: fir.store %[[AVAL]] to %[[AREF]] : !fir.ref<!fir.complex<10>>
98 subroutine div_test_extended(a,b,c)
99 complex(kind=10) :: a, b, c
100 a = b / c
101 end subroutine div_test_extended
103 ! CHECK-LABEL: @_QPdiv_test_quad
104 ! CHECK-SAME: %[[AREF:.*]]: !fir.ref<!fir.complex<16>> {{.*}}, %[[BREF:.*]]: !fir.ref<!fir.complex<16>> {{.*}}, %[[CREF:.*]]: !fir.ref<!fir.complex<16>> {{.*}})
105 ! CHECK: %[[BVAL:.*]] = fir.load %[[BREF]] : !fir.ref<!fir.complex<16>>
106 ! CHECK: %[[CVAL:.*]] = fir.load %[[CREF]] : !fir.ref<!fir.complex<16>>
107 ! CHECK: %[[BREAL:.*]] = fir.extract_value %[[BVAL]], [0 : index] : (!fir.complex<16>) -> f128
108 ! CHECK: %[[BIMAG:.*]] = fir.extract_value %[[BVAL]], [1 : index] : (!fir.complex<16>) -> f128
109 ! CHECK: %[[CREAL:.*]] = fir.extract_value %[[CVAL]], [0 : index] : (!fir.complex<16>) -> f128
110 ! CHECK: %[[CIMAG:.*]] = fir.extract_value %[[CVAL]], [1 : index] : (!fir.complex<16>) -> f128
111 ! CHECK: %[[AVAL:.*]] = fir.call @__divtc3(%[[BREAL]], %[[BIMAG]], %[[CREAL]], %[[CIMAG]]) fastmath<contract> : (f128, f128, f128, f128) -> !fir.complex<16>
112 ! CHECK: fir.store %[[AVAL]] to %[[AREF]] : !fir.ref<!fir.complex<16>>
113 subroutine div_test_quad(a,b,c)
114 complex(kind=16) :: a, b, c
115 a = b / c
116 end subroutine div_test_quad