xref: /llvm-project/flang/test/Lower/sqrt.f90 (revision c4204c0b29a6721267b1bcbaeedd7b1118e42396)
1! RUN: bbc -emit-fir -outline-intrinsics %s -o - | FileCheck %s --check-prefixes="CHECK,CMPLX-PRECISE"
2! RUN: bbc --math-runtime=precise -emit-fir -outline-intrinsics %s -o - | FileCheck %s --check-prefixes="CMPLX-PRECISE"
3! RUN: bbc --force-mlir-complex -emit-fir -outline-intrinsics %s -o - | FileCheck %s --check-prefixes="CMPLX-FAST"
4! RUN: %flang_fc1 -emit-fir -mllvm -outline-intrinsics %s -o - | FileCheck %s --check-prefixes="CHECK,CMPLX-PRECISE"
5! RUN: %flang_fc1 -fapprox-func -emit-fir -mllvm -outline-intrinsics %s -o - | FileCheck %s --check-prefixes="CMPLX-FAST"
6! RUN: %flang_fc1 -emit-fir -mllvm --math-runtime=precise -mllvm -outline-intrinsics %s -o - | FileCheck %s --check-prefixes="CMPLX-PRECISE"
7! RUN: %flang_fc1 -emit-fir -mllvm --force-mlir-complex -mllvm -outline-intrinsics %s -o - | FileCheck %s --check-prefixes="CMPLX-FAST"
8
9! CHECK-LABEL: sqrt_testr
10subroutine sqrt_testr(a, b)
11  real :: a, b
12! CHECK: fir.call @fir.sqrt.contract.f32.f32
13  b = sqrt(a)
14end subroutine
15
16! CHECK-LABEL: sqrt_testd
17subroutine sqrt_testd(a, b)
18  real(kind=8) :: a, b
19! CHECK: fir.call @fir.sqrt.contract.f64.f64
20  b = sqrt(a)
21end subroutine
22
23! CHECK-LABEL: sqrt_testc
24subroutine sqrt_testc(z)
25  complex :: z
26! CHECK: fir.call @fir.sqrt.contract.z32.z32
27  z = sqrt(z)
28end subroutine
29
30! CHECK-LABEL: sqrt_testcd
31subroutine sqrt_testcd(z)
32  complex(kind=8) :: z
33! CHECK: fir.call @fir.sqrt.contract.z64.z64
34  z = sqrt(z)
35end subroutine
36
37! CHECK-LABEL: @fir.sqrt.contract.f32.f32
38! CHECK: math.sqrt %{{.*}} : f32
39
40! CHECK-LABEL: @fir.sqrt.contract.f64.f64
41! CHECK: math.sqrt %{{.*}} : f64
42
43! CHECK-LABEL: func private @fir.sqrt.contract.z32.z32
44! CMPLX-FAST: complex.sqrt %{{.*}} : complex<f32>
45! CMPLX-PRECISE: fir.call @csqrtf
46
47! CHECK-LABEL: @fir.sqrt.contract.z64.z64
48! CMPLX-FAST: complex.sqrt %{{.*}} : complex<f64>
49! CMPLX-PRECISE: fir.call @csqrt
50