Revert "[InstCombine] Support gep nuw in icmp folds" (#118698)
[llvm-project.git] / flang / test / Lower / HLFIR / expr-as-inquired.f90
blob455ddf6a442810547f841af6dcb87c730ea088dc
1 ! Test lowering to HLFIR of the intrinsic lowering framework
2 ! "asInquired" option.
4 ! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
6 subroutine test_isAllocated(x, l)
7 logical :: l
8 real, allocatable :: x(:)
9 l = allocated(x)
10 end subroutine
11 ! CHECK-LABEL: func.func @_QPtest_isallocated(
12 ! CHECK: %[[VAL_2:.*]]:2 = hlfir.declare %{{.*}} {{.*}}El
13 ! CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %{{.*}} {fortran_attrs = #fir.var_attrs<allocatable>, {{.*}}Ex"
14 ! CHECK: %[[VAL_4:.*]] = fir.load %[[VAL_3]]#1 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>
15 ! CHECK: %[[VAL_5:.*]] = fir.box_addr %[[VAL_4]] : (!fir.box<!fir.heap<!fir.array<?xf32>>>) -> !fir.heap<!fir.array<?xf32>>
16 ! CHECK: %[[VAL_6:.*]] = fir.convert %[[VAL_5]] : (!fir.heap<!fir.array<?xf32>>) -> i64
17 ! CHECK: %[[VAL_7:.*]] = arith.constant 0 : i64
18 ! CHECK: %[[VAL_8:.*]] = arith.cmpi ne, %[[VAL_6]], %[[VAL_7]] : i64
19 ! CHECK: %[[VAL_9:.*]] = fir.convert %[[VAL_8]] : (i1) -> !fir.logical<4>
20 ! CHECK: hlfir.assign %[[VAL_9]] to %[[VAL_2]]#0 : !fir.logical<4>, !fir.ref<!fir.logical<4>>
21 ! CHECK: return
22 ! CHECK: }
24 subroutine test_lbound(x, n)
25 integer :: n
26 real :: x(2:, 3:)
27 n = lbound(x, dim=n)
28 end subroutine
29 ! CHECK-LABEL: func.func @_QPtest_lbound(
30 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}} {{.*}}En
31 ! CHECK: %[[VAL_5:.*]] = arith.constant 2 : i64
32 ! CHECK: %[[VAL_6:.*]] = fir.convert %[[VAL_5]] : (i64) -> index
33 ! CHECK: %[[VAL_7:.*]] = arith.constant 3 : i64
34 ! CHECK: %[[VAL_8:.*]] = fir.convert %[[VAL_7]] : (i64) -> index
35 ! CHECK: %[[VAL_10:.*]]:2 = hlfir.declare %{{.*}}(%{{.*}}) {{.*}}Ex
36 ! CHECK: %[[VAL_11:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<i32>
37 ! CHECK: %[[VAL_12:.*]] = fir.shift %[[VAL_6]], %[[VAL_8]] : (index, index) -> !fir.shift<2>
38 ! CHECK: %[[VAL_13:.*]] = fir.rebox %[[VAL_10]]#1(%[[VAL_12]]) : (!fir.box<!fir.array<?x?xf32>>, !fir.shift<2>) -> !fir.box<!fir.array<?x?xf32>>
39 ! CHECK: %[[VAL_16:.*]] = fir.convert %[[VAL_13]] : (!fir.box<!fir.array<?x?xf32>>) -> !fir.box<none>
40 ! CHECK: %[[VAL_18:.*]] = fir.call @_FortranALboundDim(%[[VAL_16]],
41 ! CHECK: %[[VAL_19:.*]] = fir.convert %[[VAL_18]] : (i64) -> i32
42 ! CHECK: hlfir.assign %[[VAL_19]] to %[[VAL_4]]#0 : i32, !fir.ref<i32>