[OffloadBundler] Compress bundles over 4GB (#122307)
[llvm-project.git] / flang / test / Lower / math-name-conflict.f90
blob0e20f63cf132eeb83004a2f2418edfebd76eeb44
1 ! REQUIRES: asserts
2 ! RUN: bbc -emit-fir %s --math-runtime=precise -o - | FileCheck -check-prefix=CHECK %s
3 ! RUN: bbc -emit-fir %s --math-runtime=precise -debug-only=flang-lower-intrinsic,flang-lower-expr 2>&1 | FileCheck -check-prefix=CHECK-WARN %s
5 ! CHECK-LABEL: func.func @_QPtest
6 ! CHECK: fir.call @atanh({{[^,]*}}){{.*}}: (i32) -> i32
7 ! CHECK-LABEL: func.func @_QPtest2
8 ! CHECK: %[[ADDR:.*]] = fir.address_of(@atanh) : (i32) -> i32
9 ! CHECK: %[[CAST:.*]] = fir.convert %[[ADDR]] : ((i32) -> i32) -> ((f64) -> f64)
10 ! CHECK: fir.call %[[CAST]]({{[^,]*}}){{.*}}: (f64) -> f64
12 subroutine test(x)
13 interface
14 integer function atanh(x) bind(c)
15 integer,Value :: x
16 end function atanh
17 end interface
18 integer :: x
19 print *,atanh(x)
20 end subroutine test
21 subroutine test2(x)
22 real(8) :: x
23 print *,atanh(x)
24 end subroutine test2
26 ! CHECK-LABEL: func.func @_QPtest3
27 ! CHECK: fir.call @asinh({{[^,]*}}){{.*}}: (f64) -> f64
28 ! CHECK-LABEL: func.func @_QPtest4
29 ! CHECK: %[[ADDR:.*]] = fir.address_of(@asinh) : (f64) -> f64
30 ! CHECK: %[[CAST:.*]] = fir.convert %[[ADDR]] : ((f64) -> f64) -> ((i32) -> i32)
31 ! CHECK: fir.call %[[CAST]]({{[^,]*}}){{.*}}: (i32) -> i32
32 subroutine test3(x)
33 real(8) :: x
34 print *,asinh(x)
35 end subroutine test3
36 subroutine test4(x)
37 interface
38 integer function asinh(x) bind(c)
39 integer,Value :: x
40 end function asinh
41 end interface
42 integer :: x
43 print *,asinh(x)
44 end subroutine test4
46 ! CHECK-WARN: warning: loc({{.*}}math-name-conflict.f90{{.*}}): function
47 ! CHECK-WARN-SAME: signature mismatch for 'atanh' may lead to undefined behavior.
48 ! CHECK-WARN: warning: loc({{.*}}math-name-conflict.f90{{.*}}): function
49 ! CHECK-WARN-SAME: name 'asinh' conflicts with a runtime function
50 ! CHECK-WARN-SAME: name used by Flang - this may lead to undefined behavior