Skip to content

Commit 971237d

Browse files
authored
[flang] Retain internal and BIND(C) host procedure link in FIR (#87796)
Currently, it is not possible to find back which fun.func is the host procedure of some internal procedure because the mangling of the internal procedure does not contain info about the BIND(C) name of the host. This info may be useful to ensure dwarf DW_TAG_subprogram of internal procedures are nested under DW_TAG_subprogram of host procedures for instance.
1 parent d9a5aa8 commit 971237d

16 files changed

+119
-69
lines changed

flang/include/flang/Lower/CallInterface.h

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -391,9 +391,6 @@ class CallerInterface : public CallInterface<CallerInterface> {
391391
llvm_unreachable("getting host associated type in CallerInterface");
392392
}
393393

394-
/// Set attributes on MLIR function.
395-
void setFuncAttrs(mlir::func::FuncOp) const {}
396-
397394
private:
398395
/// Check that the input vector is complete.
399396
bool verifyActualInputs() const;
@@ -444,7 +441,6 @@ class CalleeInterface : public CallInterface<CalleeInterface> {
444441
bool hasHostAssociated() const;
445442
mlir::Type getHostAssociatedTy() const;
446443
mlir::Value getHostAssociatedTuple() const;
447-
void setFuncAttrs(mlir::func::FuncOp) const;
448444

449445
private:
450446
Fortran::lower::pft::FunctionLikeUnit &funit;

flang/include/flang/Optimizer/Dialect/FIROpsSupport.h

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -104,9 +104,9 @@ static constexpr llvm::StringRef getHostAssocAttrName() {
104104
return "fir.host_assoc";
105105
}
106106

107-
/// Attribute to mark an internal procedure.
108-
static constexpr llvm::StringRef getInternalProcedureAttrName() {
109-
return "fir.internal_proc";
107+
/// Attribute to link an internal procedure to its host procedure symbol.
108+
static constexpr llvm::StringRef getHostSymbolAttrName() {
109+
return "fir.host_symbol";
110110
}
111111

112112
/// Attribute containing the original name of a function from before the
@@ -122,8 +122,8 @@ bool hasHostAssociationArgument(mlir::func::FuncOp func);
122122
/// Is the function, \p func an internal procedure ?
123123
/// Some internal procedures may have access to saved host procedure
124124
/// variables even when they do not have a tuple argument.
125-
inline bool isInternalPorcedure(mlir::func::FuncOp func) {
126-
return func->hasAttr(fir::getInternalProcedureAttrName());
125+
inline bool isInternalProcedure(mlir::func::FuncOp func) {
126+
return func->hasAttr(fir::getHostSymbolAttrName());
127127
}
128128

129129
/// Tell if \p value is:

flang/lib/Lower/CallInterface.cpp

Lines changed: 28 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -575,20 +575,41 @@ mlir::Value Fortran::lower::CalleeInterface::getHostAssociatedTuple() const {
575575
return converter.hostAssocTupleValue();
576576
}
577577

578-
void Fortran::lower::CalleeInterface::setFuncAttrs(
579-
mlir::func::FuncOp func) const {
580-
if (funit.parentHasHostAssoc())
581-
func->setAttr(fir::getInternalProcedureAttrName(),
582-
mlir::UnitAttr::get(func->getContext()));
583-
}
584-
585578
//===----------------------------------------------------------------------===//
586579
// CallInterface implementation: this part is common to both caller and callee.
587580
//===----------------------------------------------------------------------===//
588581

589582
static void addSymbolAttribute(mlir::func::FuncOp func,
590583
const Fortran::semantics::Symbol &sym,
591584
mlir::MLIRContext &mlirContext) {
585+
const Fortran::semantics::Symbol &ultimate = sym.GetUltimate();
586+
// The link between an internal procedure and its host procedure is lost
587+
// in FIR if the host is BIND(C) since the internal mangling will not
588+
// allow retrieving the host bind(C) name, and therefore func.func symbol.
589+
// Preserve it as an attribute so that this can be later retrieved.
590+
if (Fortran::semantics::ClassifyProcedure(ultimate) ==
591+
Fortran::semantics::ProcedureDefinitionClass::Internal) {
592+
if (ultimate.owner().kind() ==
593+
Fortran::semantics::Scope::Kind::Subprogram) {
594+
if (const Fortran::semantics::Symbol *hostProcedure =
595+
ultimate.owner().symbol()) {
596+
std::string hostName = Fortran::lower::mangle::mangleName(
597+
*hostProcedure, /*keepExternalInScope=*/true);
598+
func->setAttr(
599+
fir::getHostSymbolAttrName(),
600+
mlir::SymbolRefAttr::get(
601+
&mlirContext, mlir::StringAttr::get(&mlirContext, hostName)));
602+
}
603+
} else if (ultimate.owner().kind() ==
604+
Fortran::semantics::Scope::Kind::MainProgram) {
605+
func->setAttr(fir::getHostSymbolAttrName(),
606+
mlir::SymbolRefAttr::get(
607+
&mlirContext,
608+
mlir::StringAttr::get(
609+
&mlirContext, fir::NameUniquer::doProgramEntry())));
610+
}
611+
}
612+
592613
// Only add this on bind(C) functions for which the symbol is not reflected in
593614
// the current context.
594615
if (!Fortran::semantics::IsBindCProcedure(sym))
@@ -686,7 +707,6 @@ void Fortran::lower::CallInterface<T>::declare() {
686707
for (const auto &placeHolder : llvm::enumerate(inputs))
687708
if (!placeHolder.value().attributes.empty())
688709
func.setArgAttrs(placeHolder.index(), placeHolder.value().attributes);
689-
side().setFuncAttrs(func);
690710

691711
setCUDAAttributes(func, side().getProcedureSymbol(), characteristic);
692712
}
@@ -1599,10 +1619,6 @@ class SignatureBuilder
15991619
return proc;
16001620
}
16011621

1602-
/// Set internal procedure attribute on MLIR function. Internal procedure
1603-
/// are defined in the current file and will not go through SignatureBuilder.
1604-
void setFuncAttrs(mlir::func::FuncOp) const {}
1605-
16061622
/// This is not the description of an indirect call.
16071623
static constexpr bool isIndirectCall() { return false; }
16081624

flang/lib/Optimizer/Transforms/ArrayValueCopy.cpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -728,7 +728,7 @@ conservativeCallConflict(llvm::ArrayRef<mlir::Operation *> reaches) {
728728
if (auto callee =
729729
call.getCallableForCallee().dyn_cast<mlir::SymbolRefAttr>()) {
730730
auto module = op->getParentOfType<mlir::ModuleOp>();
731-
return isInternalPorcedure(
731+
return isInternalProcedure(
732732
module.lookupSymbol<mlir::func::FuncOp>(callee));
733733
}
734734
return false;
Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,39 @@
1+
! Test fir.host_sym attribute to retain link between internal
2+
! and host procedure in FIR even when BIND(C) is involved.
3+
4+
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
5+
! RUN: bbc -emit-hlfir -o - %s | fir-opt -external-name-interop -o - |FileCheck %s --check-prefix=AFTER_RENAME_PASS
6+
7+
subroutine foo() bind(c, name="some_c_name")
8+
call bar()
9+
contains
10+
subroutine bar()
11+
end subroutine
12+
end subroutine
13+
! CHECK: func.func @some_c_name()
14+
! CHECK: func.func private @_QFfooPbar() attributes {fir.host_symbol = @some_c_name, llvm.linkage = #llvm.linkage<internal>}
15+
! AFTER_RENAME_PASS: func.func @some_c_name()
16+
! AFTER_RENAME_PASS: func.func private @_QFfooPbar() attributes {fir.host_symbol = @some_c_name, llvm.linkage = #llvm.linkage<internal>}
17+
18+
subroutine notbindc()
19+
call bar()
20+
contains
21+
subroutine bar()
22+
end subroutine
23+
end subroutine
24+
! CHECK: func.func @_QPnotbindc()
25+
! CHECK: func.func private @_QFnotbindcPbar() attributes {fir.host_symbol = @_QPnotbindc, llvm.linkage = #llvm.linkage<internal>}
26+
! AFTER_RENAME_PASS: func.func @notbindc_() attributes {fir.internal_name = "_QPnotbindc"}
27+
! AFTER_RENAME_PASS: func.func private @_QFnotbindcPbar() attributes {fir.host_symbol = @notbindc_, llvm.linkage = #llvm.linkage<internal>}
28+
29+
30+
! Main program
31+
call bar()
32+
contains
33+
subroutine bar()
34+
end subroutine
35+
end
36+
! CHECK: func.func @_QQmain()
37+
! CHECK: func.func private @_QFPbar() attributes {fir.host_symbol = @_QQmain, llvm.linkage = #llvm.linkage<internal>}
38+
! AFTER_RENAME_PASS: func.func @_QQmain()
39+
! AFTER_RENAME_PASS: func.func private @_QFPbar() attributes {fir.host_symbol = @_QQmain, llvm.linkage = #llvm.linkage<internal>}

flang/test/Lower/HLFIR/internal-procedures.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ subroutine internal
1010
end subroutine
1111
end subroutine
1212
! CHECK-LABEL: func.func private @_QFtest_explicit_shape_arrayPinternal(
13-
! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<tuple<!fir.box<!fir.array<?xf32>>>> {fir.host_assoc}) attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
13+
! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<tuple<!fir.box<!fir.array<?xf32>>>> {fir.host_assoc}) attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
1414
! CHECK: %[[VAL_1:.*]] = arith.constant 0 : i32
1515
! CHECK: %[[VAL_2:.*]] = fir.coordinate_of %[[VAL_0]], %[[VAL_1]] : (!fir.ref<tuple<!fir.box<!fir.array<?xf32>>>>, i32) -> !fir.ref<!fir.box<!fir.array<?xf32>>>
1616
! CHECK: %[[VAL_3:.*]] = fir.load %[[VAL_2]] : !fir.ref<!fir.box<!fir.array<?xf32>>>
@@ -28,7 +28,7 @@ subroutine internal
2828
end subroutine
2929
end subroutine
3030
! CHECK-LABEL: func.func private @_QFtest_assumed_shapePinternal(
31-
! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<tuple<!fir.box<!fir.array<?xf32>>>> {fir.host_assoc}) attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
31+
! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<tuple<!fir.box<!fir.array<?xf32>>>> {fir.host_assoc}) attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
3232
! CHECK: %[[VAL_1:.*]] = arith.constant 0 : i32
3333
! CHECK: %[[VAL_2:.*]] = fir.coordinate_of %[[VAL_0]], %[[VAL_1]] : (!fir.ref<tuple<!fir.box<!fir.array<?xf32>>>>, i32) -> !fir.ref<!fir.box<!fir.array<?xf32>>>
3434
! CHECK: %[[VAL_3:.*]] = fir.load %[[VAL_2]] : !fir.ref<!fir.box<!fir.array<?xf32>>>
@@ -45,7 +45,7 @@ subroutine internal()
4545
end subroutine
4646
end subroutine
4747
! CHECK-LABEL: func.func private @_QFtest_scalar_charPinternal(
48-
! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<tuple<!fir.boxchar<1>>> {fir.host_assoc}) attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
48+
! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<tuple<!fir.boxchar<1>>> {fir.host_assoc}) attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
4949
! CHECK: %[[VAL_1:.*]] = arith.constant 0 : i32
5050
! CHECK: %[[VAL_2:.*]] = fir.coordinate_of %[[VAL_0]], %[[VAL_1]] : (!fir.ref<tuple<!fir.boxchar<1>>>, i32) -> !fir.ref<!fir.boxchar<1>>
5151
! CHECK: %[[VAL_3:.*]] = fir.load %[[VAL_2]] : !fir.ref<!fir.boxchar<1>>

flang/test/Lower/OpenACC/acc-routine04.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -31,4 +31,4 @@ subroutine sub2()
3131
! CHECK: acc.routine @acc_routine_0 func(@_QMdummy_modPsub1) seq
3232
! CHECK: func.func @_QMdummy_modPsub1(%arg0: !fir.ref<i32> {fir.bindc_name = "i"}) attributes {acc.routine_info = #acc.routine_info<[@acc_routine_0]>}
3333
! CHECK: func.func @_QQmain() attributes {fir.bindc_name = "test_acc_routine"}
34-
! CHECK: func.func private @_QFPsub2() attributes {acc.routine_info = #acc.routine_info<[@acc_routine_1]>, llvm.linkage = #llvm.linkage<internal>}
34+
! CHECK: func.func private @_QFPsub2() attributes {acc.routine_info = #acc.routine_info<[@acc_routine_1]>, fir.host_symbol = @_QQmain, llvm.linkage = #llvm.linkage<internal>}

flang/test/Lower/OpenMP/threadprivate-host-association-2.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@
1212
!CHECK: fir.call @_QFPsub() fastmath<contract> : () -> ()
1313
!CHECK: return
1414
!CHECK: }
15-
!CHECK: func.func private @_QFPsub() attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
15+
!CHECK: func.func private @_QFPsub() attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
1616
!CHECK: %[[A:.*]] = fir.alloca i32 {bindc_name = "a", uniq_name = "_QFEa"}
1717
!CHECK: %[[A_DECL:.*]]:2 = hlfir.declare %[[A]] {uniq_name = "_QFEa"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
1818
!CHECK: %[[A_ADDR:.*]] = fir.address_of(@_QFEa) : !fir.ref<i32>

flang/test/Lower/OpenMP/threadprivate-host-association.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@
1111
!CHECK: fir.call @_QFPsub() fastmath<contract> : () -> ()
1212
!CHECK: return
1313
!CHECK: }
14-
!CHECK: func.func private @_QFPsub() attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
14+
!CHECK: func.func private @_QFPsub() attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
1515
!CHECK: %[[A:.*]] = fir.address_of(@_QFEa) : !fir.ref<i32>
1616
!CHECK: %[[A_DECL:.*]]:2 = hlfir.declare %[[A]] {uniq_name = "_QFEa"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
1717
!CHECK: %[[TP_A:.*]] = omp.threadprivate %[[A_DECL]]#1 : !fir.ref<i32> -> !fir.ref<i32>

flang/test/Lower/character-elemental.f90

Lines changed: 7 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,12 @@ subroutine substring_main
55
character*7 :: string(2) = ['12 ', '12 ']
66
integer :: result(2)
77
integer :: ival
8+
interface
9+
elemental function inner(arg)
10+
character(len=*), intent(in) :: arg
11+
integer :: inner
12+
end function inner
13+
end interface
814

915
ival = 1
1016
! CHECK: %[[a0:.*]] = fir.alloca i32 {bindc_name = "ival", uniq_name = "_QFsubstring_mainEival"}
@@ -26,14 +32,7 @@ subroutine substring_main
2632
! CHECK: %[[a14:.*]] = fir.coordinate_of %[[a13]], %[[a12]] : (!fir.ref<!fir.array<7x!fir.char<1>>>, index) -> !fir.ref<!fir.char<1>>
2733
! CHECK: %[[a15:.*]] = fir.convert %[[a14]] : (!fir.ref<!fir.char<1>>) -> !fir.ref<!fir.char<1,?>>
2834
! CHECK: %[[a16:.*]] = fir.emboxchar %[[a15]], {{.*}} : (!fir.ref<!fir.char<1,?>>, index) -> !fir.boxchar<1>
29-
! CHECK: %[[a17:.*]] = fir.call @_QFsubstring_mainPinner(%[[a16]]) {{.*}}: (!fir.boxchar<1>) -> i32
35+
! CHECK: %[[a17:.*]] = fir.call @_QPinner(%[[a16]]) {{.*}}: (!fir.boxchar<1>) -> i32
3036
result = inner(string(1:2)(ival:ival))
3137
print *, result
32-
contains
33-
elemental function inner(arg)
34-
character(len=*), intent(in) :: arg
35-
integer :: inner
36-
37-
inner = len(arg)
38-
end function inner
3938
end subroutine substring_main

flang/test/Lower/equivalence-with-host-assoc.f90

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ subroutine inner
1010
i1 = j1
1111
end subroutine inner
1212
end subroutine test1
13-
! FIR-LABEL: func.func private @_QFtest1Pinner() attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
13+
! FIR-LABEL: func.func private @_QFtest1Pinner() attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
1414
! FIR: %[[VAL_0:.*]] = fir.address_of(@_QFtest1Ei1) : !fir.ref<!fir.array<1xi32>>
1515
! FIR: %[[VAL_1:.*]] = fir.convert %[[VAL_0]] : (!fir.ref<!fir.array<1xi32>>) -> !fir.ref<!fir.array<4xi8>>
1616
! FIR: %[[VAL_2:.*]] = arith.constant 0 : index
@@ -24,7 +24,7 @@ end subroutine test1
2424
! FIR: return
2525
! FIR: }
2626

27-
! HLFIR-LABEL: func.func private @_QFtest1Pinner() attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
27+
! HLFIR-LABEL: func.func private @_QFtest1Pinner() attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
2828
! HLFIR: %[[VAL_0:.*]] = fir.address_of(@_QFtest1Ei1) : !fir.ref<!fir.array<1xi32>>
2929
! HLFIR: %[[VAL_1:.*]] = fir.convert %[[VAL_0]] : (!fir.ref<!fir.array<1xi32>>) -> !fir.ref<!fir.array<4xi8>>
3030
! HLFIR: %[[VAL_2:.*]] = arith.constant 0 : index
@@ -54,7 +54,7 @@ subroutine inner
5454
end subroutine inner
5555
end subroutine host
5656
end module test2
57-
! FIR-LABEL: func.func private @_QMtest2FhostPinner() attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
57+
! FIR-LABEL: func.func private @_QMtest2FhostPinner() attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
5858
! FIR: %[[VAL_0:.*]] = fir.address_of(@_QMtest2FhostEf1) : !fir.ref<!fir.array<1xi32>>
5959
! FIR: %[[VAL_1:.*]] = fir.convert %[[VAL_0]] : (!fir.ref<!fir.array<1xi32>>) -> !fir.ref<!fir.array<4xi8>>
6060
! FIR: %[[VAL_2:.*]] = arith.constant 0 : index
@@ -68,7 +68,7 @@ end module test2
6868
! FIR: return
6969
! FIR: }
7070

71-
! HLFIR-LABEL: func.func private @_QMtest2FhostPinner() attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
71+
! HLFIR-LABEL: func.func private @_QMtest2FhostPinner() attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
7272
! HLFIR: %[[VAL_0:.*]] = fir.address_of(@_QMtest2FhostEf1) : !fir.ref<!fir.array<1xi32>>
7373
! HLFIR: %[[VAL_1:.*]] = fir.convert %[[VAL_0]] : (!fir.ref<!fir.array<1xi32>>) -> !fir.ref<!fir.array<4xi8>>
7474
! HLFIR: %[[VAL_2:.*]] = arith.constant 0 : index
@@ -94,7 +94,7 @@ subroutine inner
9494
i1 = j1 + k1
9595
end subroutine inner
9696
end subroutine test3
97-
! FIR-LABEL: func.func private @_QFtest3Pinner() attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
97+
! FIR-LABEL: func.func private @_QFtest3Pinner() attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
9898
! FIR: %[[VAL_0:.*]] = fir.address_of(@blk_) : !fir.ref<tuple<i32>>
9999
! FIR: %[[VAL_1:.*]] = fir.convert %[[VAL_0]] : (!fir.ref<tuple<i32>>) -> !fir.ref<!fir.array<?xi8>>
100100
! FIR: %[[VAL_2:.*]] = arith.constant 0 : index
@@ -115,7 +115,7 @@ end subroutine test3
115115
! FIR: return
116116
! FIR: }
117117

118-
! HLFIR-LABEL: func.func private @_QFtest3Pinner() attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
118+
! HLFIR-LABEL: func.func private @_QFtest3Pinner() attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
119119
! HLFIR: %[[VAL_0:.*]] = fir.address_of(@blk_) : !fir.ref<tuple<i32>>
120120
! HLFIR: %[[VAL_1:.*]] = fir.convert %[[VAL_0]] : (!fir.ref<tuple<i32>>) -> !fir.ref<!fir.array<?xi8>>
121121
! HLFIR: %[[VAL_2:.*]] = arith.constant 0 : index
@@ -149,7 +149,7 @@ subroutine inner
149149
i1 = j1 + k1
150150
end subroutine inner
151151
end subroutine test4
152-
! FIR-LABEL: func.func private @_QFtest4Pinner() attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
152+
! FIR-LABEL: func.func private @_QFtest4Pinner() attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
153153
! FIR: %[[VAL_0:.*]] = fir.address_of(@blk_) : !fir.ref<tuple<i32>>
154154
! FIR: %[[VAL_1:.*]] = fir.convert %[[VAL_0]] : (!fir.ref<tuple<i32>>) -> !fir.ref<!fir.array<?xi8>>
155155
! FIR: %[[VAL_2:.*]] = arith.constant 0 : index
@@ -170,7 +170,7 @@ end subroutine test4
170170
! FIR: return
171171
! FIR: }
172172

173-
! HLFIR-LABEL: func.func private @_QFtest4Pinner() attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
173+
! HLFIR-LABEL: func.func private @_QFtest4Pinner() attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
174174
! HLFIR: %[[VAL_0:.*]] = fir.address_of(@blk_) : !fir.ref<tuple<i32>>
175175
! HLFIR: %[[VAL_1:.*]] = fir.convert %[[VAL_0]] : (!fir.ref<tuple<i32>>) -> !fir.ref<!fir.array<?xi8>>
176176
! HLFIR: %[[VAL_2:.*]] = arith.constant 0 : index

flang/test/Lower/explicit-interface-results-2.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -70,7 +70,7 @@ subroutine host4()
7070
call internal_proc_a()
7171
contains
7272
! CHECK-LABEL: func private @_QFhost4Pinternal_proc_a
73-
! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<tuple<!fir.ref<i32>>> {fir.host_assoc}) attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
73+
! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<tuple<!fir.ref<i32>>> {fir.host_assoc}) attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
7474
subroutine internal_proc_a()
7575
call takes_array(return_array())
7676
! CHECK: %[[VAL_1:.*]] = arith.constant 0 : i32
@@ -94,7 +94,7 @@ subroutine host5()
9494
implicit none
9595
call internal_proc_a()
9696
contains
97-
! CHECK-LABEL: func private @_QFhost5Pinternal_proc_a() attributes {fir.internal_proc, llvm.linkage = #llvm.linkage<internal>} {
97+
! CHECK-LABEL: func private @_QFhost5Pinternal_proc_a() attributes {fir.host_symbol = {{.*}}, llvm.linkage = #llvm.linkage<internal>} {
9898
subroutine internal_proc_a()
9999
call takes_array(return_array())
100100
! CHECK: %[[VAL_0:.*]] = fir.address_of(@_QMsome_moduleEn_module) : !fir.ref<i32>

0 commit comments

Comments
 (0)