Skip to content

Commit 4ccd894

Browse files
committed
[Flang][OpenMP] Make implicitly captured scalars fully firstprivatized (llvm#147442)
Currently, we indicate to the runtime that implicit scalar captures are firstprivate (via map and capture types), enough for the runtime trace to treat it as such, but we do not CodeGen the IR in such a way that we can take full advantage of this aspect of the OpenMP specification. This patch seeks to change that by applying the correct symbol flags (firstprivate/implicit) to the implicitly captured scalars within target regions, which then triggers the delayed privitization code generation for these symbols, bringing the code generation in-line with the explicit firstpriviate clause. Currently, similarly to the delayed privitization I have sheltered this segment of code behind the EnabledDelayedPrivitization flag, as without it, we'll trigger an compiler error for firstprivate not being supported any time we implicitly capture a scalar and try to firstprivitize it, in future when this flag is removed it can also be removed here. So, for now, you need to enable this via providing the compiler the flag on compilation of any programs.
1 parent ae68759 commit 4ccd894

13 files changed

+224
-91
lines changed

flang/lib/Lower/OpenMP/DataSharingProcessor.cpp

Lines changed: 6 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -48,24 +48,8 @@ static bool isConstructWithTopLevelTarget(lower::pft::Evaluation &eval) {
4848
const auto *ompEval = eval.getIf<parser::OpenMPConstruct>();
4949
if (ompEval) {
5050
auto dir = parser::omp::GetOmpDirectiveName(*ompEval).v;
51-
switch (dir) {
52-
case llvm::omp::Directive::OMPD_target:
53-
case llvm::omp::Directive::OMPD_target_loop:
54-
case llvm::omp::Directive::OMPD_target_parallel_do:
55-
case llvm::omp::Directive::OMPD_target_parallel_do_simd:
56-
case llvm::omp::Directive::OMPD_target_parallel_loop:
57-
case llvm::omp::Directive::OMPD_target_teams_distribute:
58-
case llvm::omp::Directive::OMPD_target_teams_distribute_parallel_do:
59-
case llvm::omp::Directive::OMPD_target_teams_distribute_parallel_do_simd:
60-
case llvm::omp::Directive::OMPD_target_teams_distribute_simd:
61-
case llvm::omp::Directive::OMPD_target_teams_loop:
62-
case llvm::omp::Directive::OMPD_target_simd:
51+
if (llvm::omp::topTargetSet.test(dir))
6352
return true;
64-
break;
65-
default:
66-
return false;
67-
break;
68-
}
6953
}
7054
return false;
7155
}
@@ -74,12 +58,12 @@ DataSharingProcessor::DataSharingProcessor(
7458
lower::AbstractConverter &converter, semantics::SemanticsContext &semaCtx,
7559
const List<Clause> &clauses, lower::pft::Evaluation &eval,
7660
bool shouldCollectPreDeterminedSymbols, bool useDelayedPrivatization,
77-
lower::SymMap &symTable, bool isTargetPrivitization)
61+
lower::SymMap &symTable, bool isTargetPrivatization)
7862
: converter(converter), semaCtx(semaCtx),
7963
firOpBuilder(converter.getFirOpBuilder()), clauses(clauses), eval(eval),
8064
shouldCollectPreDeterminedSymbols(shouldCollectPreDeterminedSymbols),
8165
useDelayedPrivatization(useDelayedPrivatization), symTable(symTable),
82-
isTargetPrivitization(isTargetPrivitization), visitor(semaCtx) {
66+
isTargetPrivatization(isTargetPrivatization), visitor(semaCtx) {
8367
eval.visit([&](const auto &functionParserNode) {
8468
parser::Walk(functionParserNode, visitor);
8569
});
@@ -90,11 +74,11 @@ DataSharingProcessor::DataSharingProcessor(lower::AbstractConverter &converter,
9074
lower::pft::Evaluation &eval,
9175
bool useDelayedPrivatization,
9276
lower::SymMap &symTable,
93-
bool isTargetPrivitization)
77+
bool isTargetPrivatization)
9478
: DataSharingProcessor(converter, semaCtx, {}, eval,
9579
/*shouldCollectPreDeterminedSymols=*/false,
9680
useDelayedPrivatization, symTable,
97-
isTargetPrivitization) {}
81+
isTargetPrivatization) {}
9882

9983
void DataSharingProcessor::processStep1() {
10084
collectSymbolsForPrivatization();
@@ -566,7 +550,7 @@ void DataSharingProcessor::collectSymbols(
566550
// and not be added/captured by later directives. Parallel regions
567551
// will likely want the same captures to be shared and for SIMD it's
568552
// illegal to have firstprivate clauses.
569-
if (isConstructWithTopLevelTarget(eval) && !isTargetPrivitization &&
553+
if (isConstructWithTopLevelTarget(eval) && !isTargetPrivatization &&
570554
sym->test(semantics::Symbol::Flag::OmpFirstPrivate)) {
571555
return false;
572556
}

flang/lib/Lower/OpenMP/DataSharingProcessor.h

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -93,7 +93,7 @@ class DataSharingProcessor {
9393
bool useDelayedPrivatization;
9494
llvm::SmallSet<const semantics::Symbol *, 16> mightHaveReadHostSym;
9595
lower::SymMap &symTable;
96-
bool isTargetPrivitization;
96+
bool isTargetPrivatization;
9797
OMPConstructSymbolVisitor visitor;
9898
bool privatizationDone = false;
9999

@@ -133,13 +133,13 @@ class DataSharingProcessor {
133133
lower::pft::Evaluation &eval,
134134
bool shouldCollectPreDeterminedSymbols,
135135
bool useDelayedPrivatization, lower::SymMap &symTable,
136-
bool isTargetPrivitization = false);
136+
bool isTargetPrivatization = false);
137137

138138
DataSharingProcessor(lower::AbstractConverter &converter,
139139
semantics::SemanticsContext &semaCtx,
140140
lower::pft::Evaluation &eval,
141141
bool useDelayedPrivatization, lower::SymMap &symTable,
142-
bool isTargetPrivitization = false);
142+
bool isTargetPrivatization = false);
143143

144144
// Privatisation is split into 3 steps:
145145
//

flang/lib/Lower/OpenMP/OpenMP.cpp

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2392,9 +2392,6 @@ static bool isDuplicateMappedSymbol(
23922392
concatSyms.append(mappedSyms.begin(), mappedSyms.end());
23932393

23942394
auto checkSymbol = [&](const semantics::Symbol &checkSym) {
2395-
if (llvm::is_contained(concatSyms, &checkSym))
2396-
return true;
2397-
23982395
return std::any_of(concatSyms.begin(), concatSyms.end(),
23992396
[&](auto v) { return v->GetUltimate() == checkSym; });
24002397
};

flang/lib/Optimizer/OpenMP/MapsForPrivatizedSymbols.cpp

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,7 @@ class MapsForPrivatizedSymbolsPass
5858
// Check if a value of type `type` can be passed to the kernel by value.
5959
// All kernel parameters are of pointer type, so if the value can be
6060
// represented inside of a pointer, then it can be passed by value.
61-
auto isLiteralType = [&](mlir::Type type) {
61+
auto canPassByValue = [&](mlir::Type type) {
6262
const mlir::DataLayout &dl = builder.getDataLayout();
6363
mlir::Type ptrTy = mlir::LLVM::LLVMPointerType::get(builder.getContext());
6464
uint64_t ptrSize = dl.getTypeSize(ptrTy);
@@ -112,7 +112,7 @@ class MapsForPrivatizedSymbolsPass
112112
mlir::omp::VariableCaptureKind::ByRef;
113113
if (fir::isa_trivial(fir::unwrapRefType(varPtr.getType())) ||
114114
fir::isa_char(fir::unwrapRefType(varPtr.getType()))) {
115-
if (isLiteralType(fir::unwrapRefType(varPtr.getType()))) {
115+
if (canPassByValue(fir::unwrapRefType(varPtr.getType()))) {
116116
captureKind = mlir::omp::VariableCaptureKind::ByCopy;
117117
}
118118
}

flang/lib/Semantics/resolve-directives.cpp

Lines changed: 9 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -823,11 +823,10 @@ class OmpAttributeVisitor : DirectiveAttributeVisitor<llvm::omp::Directive> {
823823
Symbol::Flag::OmpLastPrivate, Symbol::Flag::OmpReduction,
824824
Symbol::Flag::OmpLinear};
825825

826-
Symbol::Flags dataMappingAttributeFlags {
827-
Symbol::Flag::OmpMapTo, Symbol::Flag::OmpMapFrom,
828-
Symbol::Flag::OmpMapToFrom, Symbol::Flag::OmpMapStorage,
829-
Symbol::Flag::OmpMapDelete, Symbol::Flag::OmpIsDevicePtr,
830-
Symbol::Flag::OmpHasDeviceAddr};
826+
Symbol::Flags dataMappingAttributeFlags{Symbol::Flag::OmpMapTo,
827+
Symbol::Flag::OmpMapFrom, Symbol::Flag::OmpMapToFrom,
828+
Symbol::Flag::OmpMapStorage, Symbol::Flag::OmpMapDelete,
829+
Symbol::Flag::OmpIsDevicePtr, Symbol::Flag::OmpHasDeviceAddr};
831830

832831
Symbol::Flags privateDataSharingAttributeFlags{Symbol::Flag::OmpPrivate,
833832
Symbol::Flag::OmpFirstPrivate, Symbol::Flag::OmpLastPrivate};
@@ -2418,6 +2417,9 @@ static bool IsTargetCaptureImplicitlyFirstprivatizeable(const Symbol &symbol,
24182417
std::map<parser::OmpVariableCategory::Value,
24192418
parser::OmpDefaultmapClause::ImplicitBehavior>
24202419
defaultMap) {
2420+
// If a Defaultmap clause is present for the current target scope, and it has
2421+
// specified behaviour other than Firstprivate for scalars then we exit early,
2422+
// as it overrides the implicit Firstprivatization of scalars OpenMP rule.
24212423
if (!defaultMap.empty()) {
24222424
if (llvm::is_contained(
24232425
defaultMap, parser::OmpVariableCategory::Value::Scalar) &&
@@ -2441,7 +2443,7 @@ static bool IsTargetCaptureImplicitlyFirstprivatizeable(const Symbol &symbol,
24412443
// TODO: Relax restriction as we progress privitization and further
24422444
// investigate the flags we can intermix with.
24432445
if (!(dsa & (dataSharingAttributeFlags | dataMappingAttributeFlags))
2444-
.none() ||
2446+
.none() ||
24452447
!checkSym.flags().none() || semantics::IsAssumedShape(checkSym) ||
24462448
semantics::IsAllocatableOrPointer(checkSym)) {
24472449
return false;
@@ -2564,7 +2566,7 @@ void OmpAttributeVisitor::CreateImplicitSymbols(const Symbol *symbol) {
25642566

25652567
bool taskGenDir = llvm::omp::taskGeneratingSet.test(dirContext.directive);
25662568
bool targetDir = llvm::omp::allTargetSet.test(dirContext.directive);
2567-
bool parallelDir = llvm::omp::allParallelSet.test(dirContext.directive);
2569+
bool parallelDir = llvm::omp::topParallelSet.test(dirContext.directive);
25682570
bool teamsDir = llvm::omp::allTeamsSet.test(dirContext.directive);
25692571
bool isStaticStorageDuration = IsSymbolStaticStorageDuration(*symbol);
25702572

flang/test/Integration/OpenMP/map-types-and-sizes.f90

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -6,14 +6,18 @@
66
! added to this directory and sub-directories.
77
!===----------------------------------------------------------------------===!
88

9-
!RUN: %flang_fc1 -emit-llvm -fopenmp -fopenmp-version=51 -fopenmp-targets=amdgcn-amd-amdhsa %s -o - | FileCheck %s
9+
! NOTE: Do not check for false delayed privatization flag until all enable-delayed-privatization flags are switched on in amd-staging
10+
!RUN %flang_fc1 -emit-llvm -fopenmp -mmlir --enable-delayed-privatization-staging=false -fopenmp-version=51 -fopenmp-targets=amdgcn-amd-amdhsa %s -o - | FileCheck %s --check-prefixes=CHECK,CHECK-NO-FPRIV
11+
!RUN: %flang_fc1 -emit-llvm -fopenmp -mmlir --enable-delayed-privatization-staging=true -fopenmp-version=51 -fopenmp-targets=amdgcn-amd-amdhsa %s -o - | FileCheck %s --check-prefixes=CHECK,CHECK-FPRIV
12+
1013

1114
!===============================================================================
1215
! Check MapTypes for target implicit captures
1316
!===============================================================================
1417

1518
!CHECK: @.offload_sizes = private unnamed_addr constant [1 x i64] [i64 4]
16-
!CHECK: @.offload_maptypes = private unnamed_addr constant [1 x i64] [i64 289]
19+
!CHECK-FPRIV: @.offload_maptypes = private unnamed_addr constant [1 x i64] [i64 289]
20+
!CHECK-NO-FPRIV: @.offload_maptypes = private unnamed_addr constant [1 x i64] [i64 800]
1721
subroutine mapType_scalar
1822
integer :: a
1923
!$omp target
@@ -372,7 +376,8 @@ subroutine mapType_nested_derived_type_member_idx()
372376
end subroutine
373377

374378
!CHECK: @.offload_sizes{{.*}} = private unnamed_addr constant [2 x i64] [i64 8, i64 4]
375-
!CHECK: @.offload_maptypes{{.*}} = private unnamed_addr constant [2 x i64] [i64 544, i64 289]
379+
!CHECK-FPRIV: @.offload_maptypes{{.*}} = private unnamed_addr constant [2 x i64] [i64 544, i64 289]
380+
!CHECK-NO-FPRIV: @.offload_maptypes{{.*}} = private unnamed_addr constant [2 x i64] [i64 544, i64 800]
376381
subroutine mapType_c_ptr
377382
use iso_c_binding, only : c_ptr, c_loc
378383
type(c_ptr) :: a
@@ -383,7 +388,8 @@ subroutine mapType_c_ptr
383388
end subroutine mapType_c_ptr
384389

385390
!CHECK: @.offload_sizes{{.*}} = private unnamed_addr constant [1 x i64] [i64 1]
386-
!CHECK: @.offload_maptypes{{.*}} = private unnamed_addr constant [1 x i64] [i64 289]
391+
!CHECK-FPRIV: @.offload_maptypes{{.*}} = private unnamed_addr constant [1 x i64] [i64 289]
392+
!CHECK-NO-FPRIV: @.offload_maptypes{{.*}} = private unnamed_addr constant [1 x i64] [i64 800]
387393
subroutine mapType_char
388394
character :: a
389395
!$omp target
Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,42 @@
1+
! Tests delayed privatization works for implicit capture of scalars similarly to
2+
! the way it works for explicitly firstprivitized scalars.
3+
4+
! RUN: %flang_fc1 -emit-mlir -fopenmp -mmlir --enable-delayed-privatization-staging \
5+
! RUN: -o - %s 2>&1 | FileCheck %s
6+
7+
! CHECK-LABEL: omp.private {type = firstprivate} @_QFExdgfx_firstprivate_i32 : i32 copy {
8+
! CHECK: ^bb0(%{{.*}}: !fir.ref<i32>, %{{.*}}: !fir.ref<i32>):
9+
! CHECK: %{{.*}} = fir.load %{{.*}} : !fir.ref<i32>
10+
! CHECK: fir.store %{{.*}} to %{{.*}} : !fir.ref<i32>
11+
! CHECK: omp.yield(%{{.*}} : !fir.ref<i32>)
12+
! CHECK: }
13+
14+
! CHECK-LABEL: omp.private {type = firstprivate} @_QFExfpvx_firstprivate_i32 : i32 copy {
15+
! CHECK: ^bb0(%{{.*}}: !fir.ref<i32>, %{{.*}}: !fir.ref<i32>):
16+
! CHECK: %{{.*}} = fir.load %{{.*}} : !fir.ref<i32>
17+
! CHECK: fir.store %{{.*}} to %{{.*}} : !fir.ref<i32>
18+
! CHECK: omp.yield(%{{.*}} : !fir.ref<i32>)
19+
! CHECK: }
20+
21+
! CHECK: %[[VAL_0:.*]] = fir.alloca i32 {bindc_name = "xdgfx", uniq_name = "_QFExdgfx"}
22+
! CHECK: %[[VAL_1:.*]] = fir.declare %[[VAL_0]] {uniq_name = "_QFExdgfx"} : (!fir.ref<i32>) -> !fir.ref<i32>
23+
! CHECK: %[[VAL_2:.*]] = fir.alloca i32 {bindc_name = "xfpvx", uniq_name = "_QFExfpvx"}
24+
! CHECK: %[[VAL_3:.*]] = fir.declare %[[VAL_2]] {uniq_name = "_QFExfpvx"} : (!fir.ref<i32>) -> !fir.ref<i32>
25+
! CHECK: %[[VAL_4:.*]] = omp.map.info var_ptr(%[[VAL_3]] : !fir.ref<i32>, i32) map_clauses(to) capture(ByCopy) -> !fir.ref<i32>
26+
! CHECK: %[[VAL_5:.*]] = omp.map.info var_ptr(%[[VAL_1]] : !fir.ref<i32>, i32) map_clauses(to) capture(ByCopy) -> !fir.ref<i32>
27+
28+
! CHECK: omp.target map_entries(%[[VAL_4]] -> %{{.*}}, %[[VAL_5]] -> %{{.*}} : !fir.ref<i32>, !fir.ref<i32>) private(@_QFExfpvx_firstprivate_i32 %[[VAL_3]] -> %[[VAL_6:.*]] [map_idx=0], @_QFExdgfx_firstprivate_i32 %[[VAL_1]] -> %[[VAL_7:.*]] [map_idx=1] : !fir.ref<i32>, !fir.ref<i32>) {
29+
! CHECK: %{{.*}} = fir.declare %[[VAL_6]] {uniq_name = "_QFExfpvx"} : (!fir.ref<i32>) -> !fir.ref<i32>
30+
! CHECK: %{{.*}} = fir.declare %[[VAL_7]] {uniq_name = "_QFExdgfx"} : (!fir.ref<i32>) -> !fir.ref<i32>
31+
32+
program test_default_implicit_firstprivate
33+
implicit none
34+
integer :: xdgfx, xfpvx
35+
xdgfx = 1
36+
xfpvx = 2
37+
!$omp target firstprivate(xfpvx)
38+
xdgfx = 42
39+
xfpvx = 43
40+
!$omp end target
41+
write(*,*) xdgfx, xfpvx
42+
end program

flang/test/Lower/OpenMP/DelayedPrivatization/target-private-multiple-variables.f90

Lines changed: 13 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,10 @@ end subroutine target_allocatable
3737

3838
! Test the privatizer for `character`
3939
!
40+
! CHECK: omp.private {type = firstprivate}
41+
! CHECK-SAME: @[[FIRSTPRIVATE_SCALAR_SYM:[^[:space:]]+mapped_var[^[:space:]]+]]
42+
! CHECK-SAME: : [[FIRSTPRIVATE_TYPE:i32]] copy {
43+
4044
! CHECK: omp.private {type = private}
4145
! CHECK-SAME: @[[CHAR_PRIVATIZER_SYM:[^[:space:]]+char_var[^[:space:]]+]]
4246
! CHECK-SAME: : [[CHAR_TYPE:!fir.boxchar<1>]] init {
@@ -78,6 +82,7 @@ end subroutine target_allocatable
7882

7983
! Test the privatizer for `real(:)`'s lower bound
8084
!
85+
8186
! CHECK: omp.private {type = private}
8287
! CHECK-SAME: @[[LB_PRIVATIZER_SYM:[^[:space:]]+lb[^[:space:]]+]]
8388
! CHECK-SAME: : [[LB_TYPE:i64]]{{$}}
@@ -140,28 +145,29 @@ end subroutine target_allocatable
140145
! CHECK: %[[REAL_ARR_ALLOC:.*]] = fir.alloca !fir.array<?xf32>, {{.*}} {bindc_name = "real_arr", {{.*}}}
141146
! CHECK: %[[REAL_ARR_DECL:.*]]:2 = hlfir.declare %[[REAL_ARR_ALLOC]]({{.*}})
142147
! CHECK: fir.store %[[REAL_ARR_DECL]]#0 to %[[REAL_ARR_DESC_ALLOCA]] : !fir.ref<!fir.box<!fir.array<?xf32>>>
143-
! CHECK: %[[MAPPED_MI0:.*]] = omp.map.info var_ptr(%[[MAPPED_DECL]]#1 : !fir.ref<i32>, i32) {{.*}}
144148
! CHECK: %[[ALLOC_VAR_MEMBER:.*]] = omp.map.info var_ptr(%[[ALLOC_VAR_DECL]]#0 : !fir.ref<!fir.box<!fir.heap<i32>>>, i32)
145149
! CHECK: %[[ALLOC_VAR_MAP:.*]] = omp.map.info var_ptr(%[[ALLOC_VAR_DECL]]#0 : !fir.ref<!fir.box<!fir.heap<i32>>>, !fir.box<!fir.heap<i32>>) {{.*}} members(%[[ALLOC_VAR_MEMBER]] :
146150
! CHECK: %[[REAL_ARR_MEMBER:.*]] = omp.map.info var_ptr(%[[REAL_ARR_DESC_ALLOCA]] : !fir.ref<!fir.box<!fir.array<?xf32>>>, f32)
147151
! CHECK: %[[REAL_ARR_DESC_MAP:.*]] = omp.map.info var_ptr(%[[REAL_ARR_DESC_ALLOCA]] : !fir.ref<!fir.box<!fir.array<?xf32>>>, !fir.box<!fir.array<?xf32>>) {{.*}} members(%[[REAL_ARR_MEMBER]] :
148152
! CHECK: fir.store %[[CHAR_VAR_DECL]]#0 to %[[CHAR_VAR_DESC_ALLOCA]] : !fir.ref<!fir.boxchar<1>>
149153
! CHECK: %[[CHAR_VAR_DESC_MAP:.*]] = omp.map.info var_ptr(%[[CHAR_VAR_DESC_ALLOCA]] : !fir.ref<!fir.boxchar<1>>, !fir.boxchar<1>)
154+
! CHECK: %[[MAPPED_MI0:.*]] = omp.map.info var_ptr(%[[MAPPED_DECL]]#0 : !fir.ref<i32>, i32) {{.*}}
150155
! CHECK: omp.target
151156
! CHECK-SAME: map_entries(
152-
! CHECK-SAME: %[[MAPPED_MI0]] -> %[[MAPPED_ARG0:[^,]+]],
153157
! CHECK-SAME: %[[ALLOC_VAR_MAP]] -> %[[MAPPED_ARG1:[^,]+]]
154158
! CHECK-SAME: %[[REAL_ARR_DESC_MAP]] -> %[[MAPPED_ARG2:[^,]+]]
155159
! CHECK-SAME: %[[CHAR_VAR_DESC_MAP]] -> %[[MAPPED_ARG3:.[^,]+]]
156-
! CHECK-SAME: !fir.ref<i32>, !fir.ref<!fir.box<!fir.heap<i32>>>, !fir.ref<!fir.box<!fir.array<?xf32>>>, !fir.ref<!fir.boxchar<1>>, !fir.llvm_ptr<!fir.ref<i32>>, !fir.llvm_ptr<!fir.ref<!fir.array<?xf32>>>
160+
! CHECK-SAME: %[[MAPPED_MI0]] -> %[[MAPPED_ARG0:[^,]+]]
161+
! CHECK-SAME: !fir.ref<!fir.box<!fir.heap<i32>>>, !fir.ref<!fir.box<!fir.array<?xf32>>>, !fir.ref<!fir.boxchar<1>>, !fir.ref<i32>, !fir.llvm_ptr<!fir.ref<i32>>, !fir.llvm_ptr<!fir.ref<!fir.array<?xf32>>>, !fir.ref<!fir.boxchar<1>>
157162
! CHECK-SAME: private(
158-
! CHECK-SAME: @[[ALLOC_PRIVATIZER_SYM]] %{{[^[:space:]]+}}#0 -> %[[ALLOC_ARG:[^,]+]] [map_idx=1],
163+
! CHECK-SAME: @[[ALLOC_PRIVATIZER_SYM]] %{{[^[:space:]]+}}#0 -> %[[ALLOC_ARG:[^,]+]] [map_idx=0],
159164
! CHECK-SAME: @[[REAL_PRIVATIZER_SYM]] %{{[^[:space:]]+}}#0 -> %[[REAL_ARG:[^,]+]],
160165
! CHECK-SAME: @[[LB_PRIVATIZER_SYM]] %{{[^[:space:]]+}}#0 -> %[[LB_ARG:[^,]+]],
161-
! CHECK-SAME: @[[ARR_PRIVATIZER_SYM]] %{{[^[:space:]]+}} -> %[[ARR_ARG:[^,]+]] [map_idx=2],
166+
! CHECK-SAME: @[[ARR_PRIVATIZER_SYM]] %{{[^[:space:]]+}} -> %[[ARR_ARG:[^,]+]] [map_idx=1],
162167
! CHECK-SAME: @[[COMP_PRIVATIZER_SYM]] %{{[^[:space:]]+}}#0 -> %[[COMP_ARG:[^,]+]],
163-
! CHECK-SAME: @[[CHAR_PRIVATIZER_SYM]] %{{[^[:space:]]+}}#0 -> %[[CHAR_ARG:[^,]+]] [map_idx=3] :
164-
! CHECK-SAME: !fir.ref<!fir.box<!fir.heap<i32>>>, !fir.ref<f32>, !fir.ref<i64>, !fir.ref<!fir.box<!fir.array<?xf32>>>, !fir.ref<complex<f32>>, !fir.boxchar<1>) {
168+
! CHECK-SAME: @[[CHAR_PRIVATIZER_SYM]] %{{[^[:space:]]+}}#0 -> %[[CHAR_ARG:[^,]+]] [map_idx=2]
169+
! CHECK-SAME: @[[FIRSTPRIVATE_SCALAR_SYM]] %{{[^[:space:]]+}}#0 -> %[[FP_SCALAR_ARG:[^,]+]] [map_idx=3] :
170+
! CHECK-SAME: !fir.ref<!fir.box<!fir.heap<i32>>>, !fir.ref<f32>, !fir.ref<i64>, !fir.ref<!fir.box<!fir.array<?xf32>>>, !fir.ref<complex<f32>>, !fir.boxchar<1>, !fir.ref<i32>)
165171
! CHECK-NOT: fir.alloca
166172
! CHECK: hlfir.declare %[[ALLOC_ARG]]
167173
! CHECK: hlfir.declare %[[REAL_ARG]]

0 commit comments

Comments
 (0)