[llvm-gsymutil] Disable test macho-gsym-merged-callsites-dsym (#119957)
[llvm-project.git] / flang / test / Lower / Intrinsics / dconjg.f90
blob1362b4ccf8c03ef921b7b9103253bba5e2a84562
1 ! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
3 subroutine test_dconjg(r, c)
4 complex(8), intent(out) :: r
5 complex(8), intent(in) :: c
7 ! CHECK-LABEL: func @_QPtest_dconjg(
8 ! CHECK-SAME: %[[ARG_0:.*]]: !fir.ref<complex<f64>> {fir.bindc_name = "r"},
9 ! CHECK-SAME: %[[ARG_1:.*]]: !fir.ref<complex<f64>> {fir.bindc_name = "c"}) {
10 ! CHECK: %[[VAL_0:.*]] = fir.load %[[ARG_1]] : !fir.ref<complex<f64>>
11 ! CHECK: %[[VAL_1:.*]] = fir.extract_value %[[VAL_0]], [1 : index] : (complex<f64>) -> f64
12 ! CHECK: %[[VAL_2:.*]] = arith.negf %[[VAL_1]] {{.*}}: f64
13 ! CHECK: %[[VAL_3:.*]] = fir.insert_value %[[VAL_0]], %[[VAL_2]], [1 : index] : (complex<f64>, f64) -> complex<f64>
14 ! CHECK: fir.store %[[VAL_3]] to %[[ARG_0]] : !fir.ref<complex<f64>>
15 ! CHECK: return
16 ! CHECK: }
18 r = dconjg(c)
19 end