aboutsummaryrefslogtreecommitdiff
path: root/flang/test/Lower/Intrinsics/modulo.f90
diff options
context:
space:
mode:
Diffstat (limited to 'flang/test/Lower/Intrinsics/modulo.f90')
-rw-r--r--flang/test/Lower/Intrinsics/modulo.f9018
1 files changed, 10 insertions, 8 deletions
diff --git a/flang/test/Lower/Intrinsics/modulo.f90 b/flang/test/Lower/Intrinsics/modulo.f90
index 383cb34..ac18e59 100644
--- a/flang/test/Lower/Intrinsics/modulo.f90
+++ b/flang/test/Lower/Intrinsics/modulo.f90
@@ -1,11 +1,13 @@
-! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
+! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s -check-prefixes=HONORINF,ALL
+! RUN: flang-new -fc1 -menable-no-infs -emit-fir -flang-deprecated-no-hlfir %s -o - | FileCheck %s -check-prefixes=CHECK,ALL
-! CHECK-LABEL: func @_QPmodulo_testr(
-! CHECK-SAME: %[[arg0:.*]]: !fir.ref<f64>{{.*}}, %[[arg1:.*]]: !fir.ref<f64>{{.*}}, %[[arg2:.*]]: !fir.ref<f64>{{.*}}) {
+! ALL-LABEL: func @_QPmodulo_testr(
+! ALL-SAME: %[[arg0:.*]]: !fir.ref<f64>{{.*}}, %[[arg1:.*]]: !fir.ref<f64>{{.*}}, %[[arg2:.*]]: !fir.ref<f64>{{.*}}) {
subroutine modulo_testr(r, a, p)
real(8) :: r, a, p
- ! CHECK-DAG: %[[a:.*]] = fir.load %[[arg1]] : !fir.ref<f64>
- ! CHECK-DAG: %[[p:.*]] = fir.load %[[arg2]] : !fir.ref<f64>
+ ! ALL-DAG: %[[a:.*]] = fir.load %[[arg1]] : !fir.ref<f64>
+ ! ALL-DAG: %[[p:.*]] = fir.load %[[arg2]] : !fir.ref<f64>
+ ! HONORINF: %[[res:.*]] = fir.call @_FortranAModuloReal8(%[[a]], %[[p]]
! CHECK-DAG: %[[rem:.*]] = arith.remf %[[a]], %[[p]] {{.*}}: f64
! CHECK-DAG: %[[zero:.*]] = arith.constant 0.000000e+00 : f64
! CHECK-DAG: %[[remNotZero:.*]] = arith.cmpf une, %[[rem]], %[[zero]] {{.*}} : f64
@@ -15,12 +17,12 @@ subroutine modulo_testr(r, a, p)
! CHECK-DAG: %[[mustAddP:.*]] = arith.andi %[[remNotZero]], %[[signDifferent]] : i1
! CHECK-DAG: %[[remPlusP:.*]] = arith.addf %[[rem]], %[[p]] {{.*}}: f64
! CHECK: %[[res:.*]] = arith.select %[[mustAddP]], %[[remPlusP]], %[[rem]] : f64
- ! CHECK: fir.store %[[res]] to %[[arg0]] : !fir.ref<f64>
+ ! ALL: fir.store %[[res]] to %[[arg0]] : !fir.ref<f64>
r = modulo(a, p)
end subroutine
-! CHECK-LABEL: func @_QPmodulo_testi(
-! CHECK-SAME: %[[arg0:.*]]: !fir.ref<i64>{{.*}}, %[[arg1:.*]]: !fir.ref<i64>{{.*}}, %[[arg2:.*]]: !fir.ref<i64>{{.*}}) {
+! ALL-LABEL: func @_QPmodulo_testi(
+! ALL-SAME: %[[arg0:.*]]: !fir.ref<i64>{{.*}}, %[[arg1:.*]]: !fir.ref<i64>{{.*}}, %[[arg2:.*]]: !fir.ref<i64>{{.*}}) {
subroutine modulo_testi(r, a, p)
integer(8) :: r, a, p
! CHECK-DAG: %[[a:.*]] = fir.load %[[arg1]] : !fir.ref<i64>