1 ! Test lowering of DOT_PRODUCT intrinsic to HLFIR
2 ! RUN: bbc -emit-hlfir -o - %s 2>&1 | FileCheck %s
4 ! dot product with numerical arguments
5 subroutine dot_product1(lhs
, rhs
, res
)
6 integer lhs(:), rhs(:), res
7 res
= DOT_PRODUCT(lhs
,rhs
)
9 ! CHECK-LABEL: func.func @_QPdot_product1
10 ! CHECK: %[[LHS:.*]]: !fir.box<!fir.array<?xi32>> {fir.bindc_name = "lhs"}
11 ! CHECK: %[[RHS:.*]]: !fir.box<!fir.array<?xi32>> {fir.bindc_name = "rhs"}
12 ! CHECK: %[[RES:.*]]: !fir.ref<i32> {fir.bindc_name = "res"}
13 ! CHECK-DAG: %[[LHS_VAR:.*]]:2 = hlfir.declare %[[LHS]]
14 ! CHECK-DAG: %[[RHS_VAR:.*]]:2 = hlfir.declare %[[RHS]]
15 ! CHECK-DAG: %[[RES_VAR:.*]]:2 = hlfir.declare %[[RES]]
16 ! CHECK-NEXT: %[[EXPR:.*]] = hlfir.dot_product %[[LHS_VAR]]#0 %[[RHS_VAR]]#0 {fastmath = #arith.fastmath<contract>} : (!fir.box<!fir.array<?xi32>>, !fir.box<!fir.array<?xi32>>) -> i32
17 ! CHECK-NEXT: hlfir.assign %[[EXPR]] to %[[RES_VAR]]#0 : i32, !fir.ref<i32>
21 ! dot product with logical arguments
22 subroutine dot_product2(lhs
, rhs
, res
)
23 logical lhs(:), rhs(:), res
24 res
= DOT_PRODUCT(lhs
,rhs
)
26 ! CHECK-LABEL: func.func @_QPdot_product2
27 ! CHECK: %[[LHS:.*]]: !fir.box<!fir.array<?x!fir.logical<4>>> {fir.bindc_name = "lhs"}
28 ! CHECK: %[[RHS:.*]]: !fir.box<!fir.array<?x!fir.logical<4>>> {fir.bindc_name = "rhs"}
29 ! CHECK: %[[RES:.*]]: !fir.ref<!fir.logical<4>> {fir.bindc_name = "res"}
30 ! CHECK-DAG: %[[LHS_VAR:.*]]:2 = hlfir.declare %[[LHS]]
31 ! CHECK-DAG: %[[RHS_VAR:.*]]:2 = hlfir.declare %[[RHS]]
32 ! CHECK-DAG: %[[RES_VAR:.*]]:2 = hlfir.declare %[[RES]]
33 ! CHECK-NEXT: %[[EXPR:.*]] = hlfir.dot_product %[[LHS_VAR]]#0 %[[RHS_VAR]]#0 {fastmath = #arith.fastmath<contract>} : (!fir.box<!fir.array<?x!fir.logical<4>>>, !fir.box<!fir.array<?x!fir.logical<4>>>) -> !fir.logical<4>
34 ! CHECK-NEXT: hlfir.assign %[[EXPR]] to %[[RES_VAR]]#0 : !fir.logical<4>, !fir.ref<!fir.logical<4>>
38 ! arguments are of known shape
39 subroutine dot_product3(lhs
, rhs
, res
)
40 integer lhs(5), rhs(5), res
41 res
= DOT_PRODUCT(lhs
,rhs
)
43 ! CHECK-LABEL: func.func @_QPdot_product3
44 ! CHECK: %[[LHS:.*]]: !fir.ref<!fir.array<5xi32>> {fir.bindc_name = "lhs"}
45 ! CHECK: %[[RHS:.*]]: !fir.ref<!fir.array<5xi32>> {fir.bindc_name = "rhs"}
46 ! CHECK: %[[RES:.*]]: !fir.ref<i32> {fir.bindc_name = "res"}
47 ! CHECK-DAG: %[[LHS_VAR:.*]]:2 = hlfir.declare %[[LHS]]
48 ! CHECK-DAG: %[[RHS_VAR:.*]]:2 = hlfir.declare %[[RHS]]
49 ! CHECK-DAG: %[[RES_VAR:.*]]:2 = hlfir.declare %[[RES]]
50 ! CHECK-NEXT: %[[EXPR:.*]] = hlfir.dot_product %[[LHS_VAR]]#0 %[[RHS_VAR]]#0 {fastmath = #arith.fastmath<contract>} : (!fir.ref<!fir.array<5xi32>>, !fir.ref<!fir.array<5xi32>>) -> i32
51 ! CHECK-NEXT: hlfir.assign %[[EXPR]] to %[[RES_VAR]]#0 : i32, !fir.ref<i32>
55 subroutine dot_product4(lhs
, rhs
, res
)
56 integer, allocatable
:: lhs(:), rhs(:)
58 res
= dot_product(lhs
, rhs
)
60 ! CHECK-LABEL: func.func @_QPdot_product4
61 ! CHECK: %[[LHS:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>> {fir.bindc_name = "lhs"}
62 ! CHECK: %[[RHS:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>> {fir.bindc_name = "rhs"}
63 ! CHECK: %[[RES:.*]]: !fir.ref<i32> {fir.bindc_name = "res"}
64 ! CHECK-DAG: %[[LHS_VAR:.*]]:2 = hlfir.declare %[[LHS]]
65 ! CHECK-DAG: %[[RHS_VAR:.*]]:2 = hlfir.declare %[[RHS]]
66 ! CHECK-DAG: %[[RES_VAR:.*]]:2 = hlfir.declare %[[RES]]
67 ! CHECK-NEXT: %[[LHS_LD:.*]] = fir.load %[[LHS_VAR]]#0
68 ! CHECK-NEXT: %[[RHS_LD:.*]] = fir.load %[[RHS_VAR]]#0
69 ! CHECK-NEXT: %[[PROD:.*]] = hlfir.dot_product %[[LHS_LD]] %[[RHS_LD]] {fastmath = #arith.fastmath<contract>} : (!fir.box<!fir.heap<!fir.array<?xi32>>>, !fir.box<!fir.heap<!fir.array<?xi32>>>) -> i32
70 ! CHECK-NEXT: hlfir.assign %[[PROD]] to %[[RES_VAR]]#0 : i32, !fir.ref<i32>
74 ! CHECK-LABEL: func.func @_QPdot_product5
75 ! CHECK: %[[LHS:.*]]:2 = hlfir.declare %{{.*}} dummy_scope %{{[0-9]+}} {uniq_name = "_QFdot_product5Elhs"} : (!fir.box<!fir.array<?xi32>>, !fir.dscope) -> (!fir.box<!fir.array<?xi32>>, !fir.box<!fir.array<?xi32>>)
76 ! CHECK: %[[C3:.*]] = arith.constant 3 : index
77 ! CHECK: %[[RHS_SHAPE:.*]] = fir.shape %[[C3]] : (index) -> !fir.shape<1>
78 ! CHECK: %[[RHS:.*]]:2 = hlfir.declare %{{.*}}(%[[RHS_SHAPE]]) dummy_scope %{{[0-9]+}} {uniq_name = "_QFdot_product5Erhs"} : (!fir.ref<!fir.array<3xi32>>, !fir.shape<1>, !fir.dscope) -> (!fir.ref<!fir.array<3xi32>>, !fir.ref<!fir.array<3xi32>>)
79 ! CHECK: {{.*}} = hlfir.dot_product %[[LHS]]#0 %[[RHS]]#0 {fastmath = #arith.fastmath<contract>} : (!fir.box<!fir.array<?xi32>>, !fir.ref<!fir.array<3xi32>>) -> i32
80 subroutine dot_product5(lhs
, rhs
, res
)
81 integer :: lhs(:), rhs(3)
83 res
= dot_product(lhs
, rhs
)