1 ! Test lowering of associate construct to HLFIR
2 ! RUN: bbc -emit-fir -hlfir -o - %s | FileCheck %s
4 subroutine associate_expr(x
)
10 ! CHECK-LABEL: func.func @_QPassociate_expr(
11 ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare {{.*}}Ex"
12 ! CHECK: %[[VAL_3:.*]] = arith.constant 0 : index
13 ! CHECK: %[[VAL_4:.*]]:3 = fir.box_dims %[[VAL_1]]#0, %[[VAL_3]] : (!fir.box<!fir.array<?xi32>>, index) -> (index, index, index)
14 ! CHECK: %[[VAL_6:.*]] = hlfir.elemental {{.*}}
15 ! CHECK: %[[VAL_11:.*]]:3 = hlfir.associate %[[VAL_6]]{{.*}}
16 ! CHECK: %[[VAL_13:.*]] = fir.shape %[[VAL_4]]#1 : (index) -> !fir.shape<1>
17 ! CHECK: %[[VAL_14:.*]]:2 = hlfir.declare %[[VAL_11]]#1(%[[VAL_13]]) {uniq_name = "_QFassociate_exprEy"} : (!fir.ref<!fir.array<?xi32>>, !fir.shape<1>) -> (!fir.box<!fir.array<?xi32>>, !fir.ref<!fir.array<?xi32>>)
18 ! CHECK: fir.call @_FortranAioEndIoStatement
19 ! CHECK: hlfir.end_associate %[[VAL_11]]#1, %[[VAL_11]]#2 : !fir.ref<!fir.array<?xi32>>, i1
21 subroutine associate_var(x
)
27 ! CHECK-LABEL: func.func @_QPassociate_var(
28 ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare {{.*}}Ex"
29 ! CHECK: %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_1]]#1 {uniq_name = "_QFassociate_varEy"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
30 ! CHECK: fir.call @_FortranAioEndIoStatement
33 subroutine associate_pointer(x
)
34 integer, pointer, contiguous
:: x(:)
35 ! Check that "y" has the target attribute.
40 ! CHECK-LABEL: func.func @_QPassociate_pointer(
41 ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare {{.*}}Ex"
42 ! CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xi32>>>>
43 ! CHECK: %[[VAL_3:.*]] = fir.box_addr %[[VAL_2]] : (!fir.box<!fir.ptr<!fir.array<?xi32>>>) -> !fir.ptr<!fir.array<?xi32>>
44 ! CHECK: %[[VAL_4:.*]] = arith.constant 0 : index
45 ! CHECK: %[[VAL_5:.*]]:3 = fir.box_dims %[[VAL_2]], %[[VAL_4]] : (!fir.box<!fir.ptr<!fir.array<?xi32>>>, index) -> (index, index, index)
46 ! CHECK: %[[VAL_6:.*]] = fir.shape_shift %[[VAL_5]]#0, %[[VAL_5]]#1 : (index, index) -> !fir.shapeshift<1>
47 ! CHECK: %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_3]](%[[VAL_6]]) {fortran_attrs = #fir.var_attrs<target>, uniq_name = "_QFassociate_pointerEy"} : (!fir.ptr<!fir.array<?xi32>>, !fir.shapeshift<1>) -> (!fir.box<!fir.array<?xi32>>, !fir.ptr<!fir.array<?xi32>>)
48 ! CHECK: fir.call @_FortranAioEndIoStatement
51 subroutine associate_allocatable(x
)
52 integer, allocatable
:: x(:)
57 ! CHECK-LABEL: func.func @_QPassociate_allocatable(
58 ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare {{.*}}Ex"
59 ! CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>
60 ! CHECK: %[[VAL_3:.*]] = fir.box_addr %[[VAL_2]] : (!fir.box<!fir.heap<!fir.array<?xi32>>>) -> !fir.heap<!fir.array<?xi32>>
61 ! CHECK: %[[VAL_4:.*]] = arith.constant 0 : index
62 ! CHECK: %[[VAL_5:.*]]:3 = fir.box_dims %[[VAL_2]], %[[VAL_4]] : (!fir.box<!fir.heap<!fir.array<?xi32>>>, index) -> (index, index, index)
63 ! CHECK: %[[VAL_6:.*]] = fir.shape_shift %[[VAL_5]]#0, %[[VAL_5]]#1 : (index, index) -> !fir.shapeshift<1>
64 ! CHECK: %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_3]](%[[VAL_6]]) {uniq_name = "_QFassociate_allocatableEy"} : (!fir.heap<!fir.array<?xi32>>, !fir.shapeshift<1>) -> (!fir.box<!fir.array<?xi32>>, !fir.heap<!fir.array<?xi32>>)
65 ! CHECK: fir.call @_FortranAioEndIoStatement
68 subroutine associate_optional(x
)
69 integer, optional
:: x(:)
70 ! Check that "y" is not given the optional attribute: x must be present as per
71 ! Fortran 2018 11.1.3.2 point 4.
76 ! CHECK-LABEL: func.func @_QPassociate_optional(
77 ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare {{.*}}Ex"
78 ! CHECK: %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_1]]#1 {uniq_name = "_QFassociate_optionalEy"} : (!fir.box<!fir.array<?xi32>>) -> (!fir.box<!fir.array<?xi32>>, !fir.box<!fir.array<?xi32>>)
79 ! CHECK: fir.call @_FortranAioEndIoStatement
82 subroutine associate_pointer_section(x
)
83 integer , pointer, contiguous
:: x(:)
84 associate (y
=> x(1:20:1))
88 ! CHECK-LABEL: func.func @_QPassociate_pointer_section(
89 ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare {{.*}}Ex"
90 ! CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xi32>>>>
91 ! CHECK: %[[VAL_4:.*]] = arith.constant 20 : index
92 ! CHECK: %[[VAL_6:.*]] = arith.constant 20 : index
93 ! CHECK: %[[VAL_8:.*]] = hlfir.designate %[[VAL_2]]{{.*}}
94 ! CHECK: %[[VAL_9:.*]] = fir.shape %[[VAL_6]] : (index) -> !fir.shape<1>
95 ! CHECK: %[[VAL_10:.*]]:2 = hlfir.declare %[[VAL_8]](%[[VAL_9]]) {fortran_attrs = #fir.var_attrs<target>, uniq_name = "_QFassociate_pointer_sectionEy"} : (!fir.ref<!fir.array<20xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<20xi32>>, !fir.ref<!fir.array<20xi32>>)
96 ! CHECK: fir.call @_FortranAioEndIoStatement