! Test passing mismatching rank arguments to unlimited polymorphic ! dummy with IGNORE_TKR(R). ! RUN: bbc -emit-hlfir -polymorphic-type -o - -I nowhere %s 2>&1 | FileCheck %s module m interface subroutine callee(x) class(*) :: x !dir$ ignore_tkr (r) x end subroutine callee end interface end module m subroutine test_integer_scalar use m integer :: x call callee(x) end subroutine test_integer_scalar ! CHECK-LABEL: func.func @_QPtest_integer_scalar() { ! CHECK: %[[VAL_0:.*]] = fir.alloca i32 {bindc_name = "x", uniq_name = "_QFtest_integer_scalarEx"} ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] {uniq_name = "_QFtest_integer_scalarEx"} : (!fir.ref) -> (!fir.ref, !fir.ref) ! CHECK: %[[VAL_2:.*]] = fir.embox %[[VAL_1]]#0 : (!fir.ref) -> !fir.box ! CHECK: %[[VAL_3:.*]] = fir.rebox %[[VAL_2]] : (!fir.box) -> !fir.class ! CHECK: fir.call @_QPcallee(%[[VAL_3]]) fastmath : (!fir.class) -> () ! CHECK: return ! CHECK: } subroutine test_real_explicit_shape_array use m real :: x(10) call callee(x) end subroutine test_real_explicit_shape_array ! CHECK-LABEL: func.func @_QPtest_real_explicit_shape_array() { ! CHECK: %[[VAL_0:.*]] = arith.constant 10 : index ! CHECK: %[[VAL_1:.*]] = fir.alloca !fir.array<10xf32> {bindc_name = "x", uniq_name = "_QFtest_real_explicit_shape_arrayEx"} ! CHECK: %[[VAL_2:.*]] = fir.shape %[[VAL_0]] : (index) -> !fir.shape<1> ! CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %[[VAL_1]](%[[VAL_2]]) {uniq_name = "_QFtest_real_explicit_shape_arrayEx"} : (!fir.ref>, !fir.shape<1>) -> (!fir.ref>, !fir.ref>) ! CHECK: %[[VAL_4:.*]] = fir.embox %[[VAL_3]]#0(%[[VAL_2]]) : (!fir.ref>, !fir.shape<1>) -> !fir.box> ! CHECK: %[[VAL_5:.*]] = fir.rebox %[[VAL_4]] : (!fir.box>) -> !fir.class> ! CHECK: %[[VAL_6:.*]] = fir.convert %[[VAL_5]] : (!fir.class>) -> !fir.class ! CHECK: fir.call @_QPcallee(%[[VAL_6]]) fastmath : (!fir.class) -> () ! CHECK: return ! CHECK: } subroutine test_logical_assumed_shape_array(x) use m logical :: x(:) call callee(x) end subroutine test_logical_assumed_shape_array ! CHECK-LABEL: func.func @_QPtest_logical_assumed_shape_array( ! CHECK-SAME: %[[VAL_0:.*]]: !fir.box>> {fir.bindc_name = "x"}) { ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] {uniq_name = "_QFtest_logical_assumed_shape_arrayEx"} : (!fir.box>>) -> (!fir.box>>, !fir.box>>) ! CHECK: %[[VAL_2:.*]] = fir.rebox %[[VAL_1]]#0 : (!fir.box>>) -> !fir.class> ! CHECK: %[[VAL_3:.*]] = fir.convert %[[VAL_2]] : (!fir.class>) -> !fir.class ! CHECK: fir.call @_QPcallee(%[[VAL_3]]) fastmath : (!fir.class) -> () ! CHECK: return ! CHECK: } subroutine test_real_2d_pointer(x) use m real, pointer :: x(:, :) call callee(x) end subroutine test_real_2d_pointer ! CHECK-LABEL: func.func @_QPtest_real_2d_pointer( ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref>>> {fir.bindc_name = "x"}) { ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] {fortran_attrs = #fir.var_attrs, uniq_name = "_QFtest_real_2d_pointerEx"} : (!fir.ref>>>) -> (!fir.ref>>>, !fir.ref>>>) ! CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref>>> ! CHECK: %[[VAL_3:.*]] = fir.rebox %[[VAL_2]] : (!fir.box>>) -> !fir.class>> ! CHECK: %[[VAL_4:.*]] = fir.convert %[[VAL_3]] : (!fir.class>>) -> !fir.class ! CHECK: fir.call @_QPcallee(%[[VAL_4]]) fastmath : (!fir.class) -> () ! CHECK: return ! CHECK: } subroutine test_up_assumed_shape_1d_array(x) use m class(*) :: x(:) call callee(x) end subroutine test_up_assumed_shape_1d_array ! CHECK-LABEL: func.func @_QPtest_up_assumed_shape_1d_array( ! CHECK-SAME: %[[VAL_0:.*]]: !fir.class> {fir.bindc_name = "x"}) { ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] {uniq_name = "_QFtest_up_assumed_shape_1d_arrayEx"} : (!fir.class>) -> (!fir.class>, !fir.class>) ! CHECK: %[[VAL_2:.*]] = fir.convert %[[VAL_1]]#0 : (!fir.class>) -> !fir.class ! CHECK: fir.call @_QPcallee(%[[VAL_2]]) fastmath : (!fir.class) -> () ! CHECK: return ! CHECK: } subroutine test_derived_explicit_shape_array use m type t1 real, allocatable :: a end type t1 type(t1) :: x(10) call callee(x) end subroutine test_derived_explicit_shape_array ! CHECK-LABEL: func.func @_QPtest_derived_explicit_shape_array() { ! CHECK: %[[VAL_0:.*]] = arith.constant 10 : index ! CHECK: %[[VAL_1:.*]] = fir.alloca !fir.array<10x!fir.type<_QFtest_derived_explicit_shape_arrayTt1{a:!fir.box>}>> {bindc_name = "x", uniq_name = "_QFtest_derived_explicit_shape_arrayEx"} ! CHECK: %[[VAL_2:.*]] = fir.shape %[[VAL_0]] : (index) -> !fir.shape<1> ! CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %[[VAL_1]](%[[VAL_2]]) {uniq_name = "_QFtest_derived_explicit_shape_arrayEx"} : (!fir.ref>}>>>, !fir.shape<1>) -> (!fir.ref>}>>>, !fir.ref>}>>>) ! CHECK: %[[VAL_4:.*]] = fir.shape %[[VAL_0]] : (index) -> !fir.shape<1> ! CHECK: %[[VAL_5:.*]] = fir.embox %[[VAL_3]]#1(%[[VAL_4]]) : (!fir.ref>}>>>, !fir.shape<1>) -> !fir.box>}>>> ! CHECK: %[[VAL_8:.*]] = fir.convert %[[VAL_5]] : (!fir.box>}>>>) -> !fir.box ! CHECK: %[[VAL_10:.*]] = fir.call @_FortranAInitialize(%[[VAL_8]], %{{.*}}, %{{.*}}) fastmath : (!fir.box, !fir.ref, i32) -> none ! CHECK: %[[VAL_11:.*]] = fir.embox %[[VAL_3]]#0(%[[VAL_2]]) : (!fir.ref>}>>>, !fir.shape<1>) -> !fir.box>}>>> ! CHECK: %[[VAL_12:.*]] = fir.convert %[[VAL_11]] : (!fir.box>}>>>) -> !fir.class ! CHECK: fir.call @_QPcallee(%[[VAL_12]]) fastmath : (!fir.class) -> () ! CHECK: return ! CHECK: } subroutine test_up_allocatable_2d_array(x) use m class(*), allocatable :: x(:, :) call callee(x) end subroutine test_up_allocatable_2d_array ! CHECK-LABEL: func.func @_QPtest_up_allocatable_2d_array( ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref>>> {fir.bindc_name = "x"}) { ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] {fortran_attrs = #fir.var_attrs, uniq_name = "_QFtest_up_allocatable_2d_arrayEx"} : (!fir.ref>>>) -> (!fir.ref>>>, !fir.ref>>>) ! CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref>>> ! CHECK: %[[VAL_3:.*]] = fir.rebox %[[VAL_2]] : (!fir.class>>) -> !fir.class>> ! CHECK: %[[VAL_4:.*]] = fir.convert %[[VAL_3]] : (!fir.class>>) -> !fir.class ! CHECK: fir.call @_QPcallee(%[[VAL_4]]) fastmath : (!fir.class) -> () ! CHECK: return ! CHECK: } subroutine test_up_pointer_1d_array(x) use m class(*), pointer :: x(:) call callee(x) end subroutine test_up_pointer_1d_array ! CHECK-LABEL: func.func @_QPtest_up_pointer_1d_array( ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref>>> {fir.bindc_name = "x"}) { ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] {fortran_attrs = #fir.var_attrs, uniq_name = "_QFtest_up_pointer_1d_arrayEx"} : (!fir.ref>>>) -> (!fir.ref>>>, !fir.ref>>>) ! CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref>>> ! CHECK: %[[VAL_3:.*]] = fir.rebox %[[VAL_2]] : (!fir.class>>) -> !fir.class>> ! CHECK: %[[VAL_4:.*]] = fir.convert %[[VAL_3]] : (!fir.class>>) -> !fir.class ! CHECK: fir.call @_QPcallee(%[[VAL_4]]) fastmath : (!fir.class) -> () ! CHECK: return ! CHECK: }