xref: /llvm-project/flang/test/Lower/complex-operations.f90 (revision c4204c0b29a6721267b1bcbaeedd7b1118e42396)
1! RUN: bbc -hlfir=false %s -o - | FileCheck %s
2
3! CHECK-LABEL: @_QPadd_test
4subroutine 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 {{.*}}: complex
9  a = b + c
10end subroutine add_test
11
12! CHECK-LABEL: @_QPsub_test
13subroutine 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 {{.*}}: complex
18  a = b - c
19end subroutine sub_test
20
21! CHECK-LABEL: @_QPmul_test
22subroutine 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 {{.*}}: complex
27  a = b * c
28end subroutine mul_test
29
30! CHECK-LABEL: @_QPdiv_test_half
31! CHECK-SAME: %[[AREF:.*]]: !fir.ref<complex<f16>> {{.*}}, %[[BREF:.*]]: !fir.ref<complex<f16>> {{.*}}, %[[CREF:.*]]: !fir.ref<complex<f16>> {{.*}})
32! CHECK: %[[BVAL:.*]] = fir.load %[[BREF]] : !fir.ref<complex<f16>>
33! CHECK: %[[CVAL:.*]] = fir.load %[[CREF]] : !fir.ref<complex<f16>>
34! CHECK: %[[AVAL:.*]] = complex.div %[[BVAL]], %[[CVAL]] fastmath<contract> : complex<f16>
35! CHECK: fir.store %[[AVAL]] to %[[AREF]] : !fir.ref<complex<f16>>
36subroutine div_test_half(a,b,c)
37  complex(kind=2) :: a, b, c
38  a = b / c
39end subroutine div_test_half
40
41! CHECK-LABEL: @_QPdiv_test_bfloat
42! CHECK-SAME: %[[AREF:.*]]: !fir.ref<complex<bf16>> {{.*}}, %[[BREF:.*]]: !fir.ref<complex<bf16>> {{.*}}, %[[CREF:.*]]: !fir.ref<complex<bf16>> {{.*}})
43! CHECK: %[[BVAL:.*]] = fir.load %[[BREF]] : !fir.ref<complex<bf16>>
44! CHECK: %[[CVAL:.*]] = fir.load %[[CREF]] : !fir.ref<complex<bf16>>
45! CHECK: %[[AVAL:.*]] = complex.div %[[BVAL]], %[[CVAL]] fastmath<contract> : complex<bf16>
46! CHECK: fir.store %[[AVAL]] to %[[AREF]] : !fir.ref<complex<bf16>>
47subroutine div_test_bfloat(a,b,c)
48  complex(kind=3) :: a, b, c
49  a = b / c
50end subroutine div_test_bfloat
51
52! CHECK-LABEL: @_QPdiv_test_single
53! CHECK-SAME: %[[AREF:.*]]: !fir.ref<complex<f32>> {{.*}}, %[[BREF:.*]]: !fir.ref<complex<f32>> {{.*}}, %[[CREF:.*]]: !fir.ref<complex<f32>> {{.*}})
54! CHECK: %[[BVAL:.*]] = fir.load %[[BREF]] : !fir.ref<complex<f32>>
55! CHECK: %[[CVAL:.*]] = fir.load %[[CREF]] : !fir.ref<complex<f32>>
56! CHECK: %[[BREAL:.*]] = fir.extract_value %[[BVAL]], [0 : index] : (complex<f32>) -> f32
57! CHECK: %[[BIMAG:.*]] = fir.extract_value %[[BVAL]], [1 : index] : (complex<f32>) -> f32
58! CHECK: %[[CREAL:.*]] = fir.extract_value %[[CVAL]], [0 : index] : (complex<f32>) -> f32
59! CHECK: %[[CIMAG:.*]] = fir.extract_value %[[CVAL]], [1 : index] : (complex<f32>) -> f32
60! CHECK: %[[AVAL:.*]] = fir.call @__divsc3(%[[BREAL]], %[[BIMAG]], %[[CREAL]], %[[CIMAG]]) fastmath<contract> : (f32, f32, f32, f32) -> complex<f32>
61! CHECK: fir.store %[[AVAL]] to %[[AREF]] : !fir.ref<complex<f32>>
62subroutine div_test_single(a,b,c)
63  complex(kind=4) :: a, b, c
64  a = b / c
65end subroutine div_test_single
66
67! CHECK-LABEL: @_QPdiv_test_double
68! CHECK-SAME: %[[AREF:.*]]: !fir.ref<complex<f64>> {{.*}}, %[[BREF:.*]]: !fir.ref<complex<f64>> {{.*}}, %[[CREF:.*]]: !fir.ref<complex<f64>> {{.*}})
69! CHECK: %[[BVAL:.*]] = fir.load %[[BREF]] : !fir.ref<complex<f64>>
70! CHECK: %[[CVAL:.*]] = fir.load %[[CREF]] : !fir.ref<complex<f64>>
71! CHECK: %[[BREAL:.*]] = fir.extract_value %[[BVAL]], [0 : index] : (complex<f64>) -> f64
72! CHECK: %[[BIMAG:.*]] = fir.extract_value %[[BVAL]], [1 : index] : (complex<f64>) -> f64
73! CHECK: %[[CREAL:.*]] = fir.extract_value %[[CVAL]], [0 : index] : (complex<f64>) -> f64
74! CHECK: %[[CIMAG:.*]] = fir.extract_value %[[CVAL]], [1 : index] : (complex<f64>) -> f64
75! CHECK: %[[AVAL:.*]] = fir.call @__divdc3(%[[BREAL]], %[[BIMAG]], %[[CREAL]], %[[CIMAG]]) fastmath<contract> : (f64, f64, f64, f64) -> complex<f64>
76! CHECK: fir.store %[[AVAL]] to %[[AREF]] : !fir.ref<complex<f64>>
77subroutine div_test_double(a,b,c)
78  complex(kind=8) :: a, b, c
79  a = b / c
80end subroutine div_test_double
81
82! CHECK-LABEL: @_QPdiv_test_extended
83! CHECK-SAME: %[[AREF:.*]]: !fir.ref<complex<f80>> {{.*}}, %[[BREF:.*]]: !fir.ref<complex<f80>> {{.*}}, %[[CREF:.*]]: !fir.ref<complex<f80>> {{.*}})
84! CHECK: %[[BVAL:.*]] = fir.load %[[BREF]] : !fir.ref<complex<f80>>
85! CHECK: %[[CVAL:.*]] = fir.load %[[CREF]] : !fir.ref<complex<f80>>
86! CHECK: %[[BREAL:.*]] = fir.extract_value %[[BVAL]], [0 : index] : (complex<f80>) -> f80
87! CHECK: %[[BIMAG:.*]] = fir.extract_value %[[BVAL]], [1 : index] : (complex<f80>) -> f80
88! CHECK: %[[CREAL:.*]] = fir.extract_value %[[CVAL]], [0 : index] : (complex<f80>) -> f80
89! CHECK: %[[CIMAG:.*]] = fir.extract_value %[[CVAL]], [1 : index] : (complex<f80>) -> f80
90! CHECK: %[[AVAL:.*]] = fir.call @__divxc3(%[[BREAL]], %[[BIMAG]], %[[CREAL]], %[[CIMAG]]) fastmath<contract> : (f80, f80, f80, f80) -> complex<f80>
91! CHECK: fir.store %[[AVAL]] to %[[AREF]] : !fir.ref<complex<f80>>
92subroutine div_test_extended(a,b,c)
93  complex(kind=10) :: a, b, c
94  a = b / c
95end subroutine div_test_extended
96
97! CHECK-LABEL: @_QPdiv_test_quad
98! CHECK-SAME: %[[AREF:.*]]: !fir.ref<complex<f128>> {{.*}}, %[[BREF:.*]]: !fir.ref<complex<f128>> {{.*}}, %[[CREF:.*]]: !fir.ref<complex<f128>> {{.*}})
99! CHECK: %[[BVAL:.*]] = fir.load %[[BREF]] : !fir.ref<complex<f128>>
100! CHECK: %[[CVAL:.*]] = fir.load %[[CREF]] : !fir.ref<complex<f128>>
101! CHECK: %[[BREAL:.*]] = fir.extract_value %[[BVAL]], [0 : index] : (complex<f128>) -> f128
102! CHECK: %[[BIMAG:.*]] = fir.extract_value %[[BVAL]], [1 : index] : (complex<f128>) -> f128
103! CHECK: %[[CREAL:.*]] = fir.extract_value %[[CVAL]], [0 : index] : (complex<f128>) -> f128
104! CHECK: %[[CIMAG:.*]] = fir.extract_value %[[CVAL]], [1 : index] : (complex<f128>) -> f128
105! CHECK: %[[AVAL:.*]] = fir.call @__divtc3(%[[BREAL]], %[[BIMAG]], %[[CREAL]], %[[CIMAG]]) fastmath<contract> : (f128, f128, f128, f128) -> complex<f128>
106! CHECK: fir.store %[[AVAL]] to %[[AREF]] : !fir.ref<complex<f128>>
107subroutine div_test_quad(a,b,c)
108  complex(kind=16) :: a, b, c
109  a = b / c
110end subroutine div_test_quad
111