! Test lowering of internal procedure host association for global variables ! A tuple function argument should not be created for associated globals, and ! instead globals should be instantiated with a fir.address_of inside the ! contained procedures. ! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s module test_mod_used_in_host integer :: i, j_in_equiv integer :: not_in_equiv equivalence (i,j_in_equiv) end module subroutine module_var() use test_mod_used_in_host call bar() contains subroutine bar() print *, j_in_equiv, not_in_equiv end subroutine end subroutine ! CHECK-LABEL: func.func @_QFmodule_varPbar() ! CHECK: %[[VAL_0:.*]] = fir.address_of(@_QMtest_mod_used_in_hostEi) : !fir.ref> ! CHECK: %[[VAL_1:.*]] = arith.constant 0 : index ! CHECK: %[[VAL_2:.*]] = fir.coordinate_of %[[VAL_0]], %[[VAL_1]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[VAL_3:.*]] = fir.convert %[[VAL_2]] : (!fir.ref) -> !fir.ptr ! CHECK: %[[VAL_4:.*]] = fir.address_of(@_QMtest_mod_used_in_hostEnot_in_equiv) : !fir.ref subroutine test_common() integer :: i(2) integer :: j_in_equiv integer :: not_in_equiv equivalence (i(2),j_in_equiv) common /x/ i, not_in_equiv call bar() contains subroutine bar() print *, j_in_equiv, not_in_equiv end subroutine end subroutine ! CHECK-LABEL: func.func @_QFtest_commonPbar() attributes {fir.internal_proc} { ! CHECK: %[[VAL_0:.*]] = fir.address_of(@x_) : !fir.ref> ! CHECK: %[[VAL_1:.*]] = fir.convert %[[VAL_0]] : (!fir.ref>) -> !fir.ref> ! CHECK: %[[VAL_2:.*]] = arith.constant 4 : index ! CHECK: %[[VAL_3:.*]] = fir.coordinate_of %[[VAL_1]], %[[VAL_2]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[VAL_4:.*]] = fir.convert %[[VAL_3]] : (!fir.ref) -> !fir.ptr ! CHECK: %[[VAL_5:.*]] = fir.convert %[[VAL_0]] : (!fir.ref>) -> !fir.ref> ! CHECK: %[[VAL_6:.*]] = arith.constant 8 : index ! CHECK: %[[VAL_7:.*]] = fir.coordinate_of %[[VAL_5]], %[[VAL_6]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[VAL_8:.*]] = fir.convert %[[VAL_7]] : (!fir.ref) -> !fir.ref subroutine saved_equiv() integer, save :: i(2) integer, save :: j_in_equiv integer, save :: not_in_equiv equivalence (i(2),j_in_equiv) call bar() contains subroutine bar() print *, j_in_equiv, not_in_equiv end subroutine end subroutine ! CHECK-LABEL: func.func @_QFsaved_equivPbar() attributes {fir.internal_proc} { ! CHECK: %[[VAL_0:.*]] = fir.address_of(@_QFsaved_equivEi) : !fir.ref> ! CHECK: %[[VAL_1:.*]] = arith.constant 4 : index ! CHECK: %[[VAL_2:.*]] = fir.coordinate_of %[[VAL_0]], %[[VAL_1]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[VAL_3:.*]] = fir.convert %[[VAL_2]] : (!fir.ref) -> !fir.ptr ! CHECK: %[[VAL_4:.*]] = fir.address_of(@_QFsaved_equivEnot_in_equiv) : !fir.ref subroutine mixed_capture() integer, save :: saved_i integer, save :: saved_j equivalence (saved_i, saved_j) integer :: i integer :: j equivalence (i,j) call bar() contains subroutine bar() call test(saved_j, j) end subroutine end subroutine ! CHECK-LABEL: func.func @_QFmixed_capturePbar( ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref>> {fir.host_assoc}) attributes {fir.internal_proc} { ! CHECK: %[[VAL_1:.*]] = fir.address_of(@_QFmixed_captureEsaved_i) : !fir.ref> ! CHECK: %[[VAL_2:.*]] = arith.constant 0 : index ! CHECK: %[[VAL_3:.*]] = fir.coordinate_of %[[VAL_1]], %[[VAL_2]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[VAL_4:.*]] = fir.convert %[[VAL_3]] : (!fir.ref) -> !fir.ptr ! CHECK: %[[VAL_5:.*]] = arith.constant 0 : i32 ! CHECK: %[[VAL_6:.*]] = fir.coordinate_of %[[VAL_0]], %[[VAL_5]] : (!fir.ref>>, i32) -> !fir.llvm_ptr> ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_6]] : !fir.llvm_ptr> ! CHECK: %[[VAL_9:.*]] = fir.convert %[[VAL_4]] : (!fir.ptr) -> !fir.ref ! CHECK: fir.call @_QPtest(%[[VAL_9]], %[[VAL_7]]) {{.*}} : (!fir.ref, !fir.ref) -> ()