diff --git a/flang/lib/Lower/OpenMP/ClauseProcessor.cpp b/flang/lib/Lower/OpenMP/ClauseProcessor.cpp index dd0cb3c42ba26..71ad4dd5197b0 100644 --- a/flang/lib/Lower/OpenMP/ClauseProcessor.cpp +++ b/flang/lib/Lower/OpenMP/ClauseProcessor.cpp @@ -1446,6 +1446,41 @@ void ClauseProcessor::processMapObjects( } } +/// Extract and mangle the mapper identifier name from a mapper clause. +/// Returns "__implicit_mapper" if no mapper is specified, or "default" if +/// the default mapper is specified, otherwise returns the mangled mapper name. +/// This handles both the Map clause (which uses a vector of mappers) and +/// To/From clauses (which use a DefinedOperator). +template +static std::string +getMapperIdentifier(lower::AbstractConverter &converter, + const std::optional &mapper) { + std::string mapperIdName = "__implicit_mapper"; + if (mapper) { + const semantics::Symbol *mapperSym = nullptr; + + // Handle different mapper types + if constexpr (std::is_same_v) { + // For To/From clauses: mapper is a DefinedOperator + assert(mapper->size() == 1 && "more than one mapper"); + mapperSym = mapper->front().v.id().symbol; + } else { + // For Map clause: mappers is a vector + assert(mapper->size() == 1 && "more than one mapper"); + mapperSym = mapper->front().v.id().symbol; + } + + mapperIdName = mapperSym->name().ToString(); + if (mapperIdName != "default") { + // Mangle with the ultimate owner so that use-associated mapper + // identifiers resolve to the same symbol as their defining scope. + const semantics::Symbol &ultimate = mapperSym->GetUltimate(); + mapperIdName = converter.mangleName(mapperIdName, ultimate.owner()); + } + } + return mapperIdName; +} + bool ClauseProcessor::processMap( mlir::Location currentLocation, lower::StatementContext &stmtCtx, mlir::omp::MapClauseOps &result, llvm::omp::Directive directive, @@ -1514,17 +1549,7 @@ bool ClauseProcessor::processMap( TODO(currentLocation, "Support for iterator modifiers is not implemented yet"); } - if (mappers) { - assert(mappers->size() == 1 && "more than one mapper"); - const semantics::Symbol *mapperSym = mappers->front().v.id().symbol; - mapperIdName = mapperSym->name().ToString(); - if (mapperIdName != "default") { - // Mangle with the ultimate owner so that use-associated mapper - // identifiers resolve to the same symbol as their defining scope. - const semantics::Symbol &ultimate = mapperSym->GetUltimate(); - mapperIdName = converter.mangleName(mapperIdName, ultimate.owner()); - } - } + mapperIdName = getMapperIdentifier(converter, mappers); processMapObjects(stmtCtx, clauseLocation, std::get(clause.t), mapTypeBits, @@ -1548,21 +1573,22 @@ bool ClauseProcessor::processMotionClauses(lower::StatementContext &stmtCtx, mlir::Location clauseLocation = converter.genLocation(source); const auto &[expectation, mapper, iterator, objects] = clause.t; - // TODO Support motion modifiers: mapper, iterator. - if (mapper) { - TODO(clauseLocation, "Mapper modifier is not supported yet"); - } else if (iterator) { - TODO(clauseLocation, "Iterator modifier is not supported yet"); - } - mlir::omp::ClauseMapFlags mapTypeBits = std::is_same_v, omp::clause::To> ? mlir::omp::ClauseMapFlags::to : mlir::omp::ClauseMapFlags::from; if (expectation && *expectation == omp::clause::To::Expectation::Present) mapTypeBits |= mlir::omp::ClauseMapFlags::present; + + // Support motion modifiers: mapper, iterator. + std::string mapperIdName = getMapperIdentifier(converter, mapper); + if (iterator) { + TODO(clauseLocation, "Iterator modifier is not supported yet"); + } + processMapObjects(stmtCtx, clauseLocation, objects, mapTypeBits, - parentMemberIndices, result.mapVars, mapSymbols); + parentMemberIndices, result.mapVars, mapSymbols, + mapperIdName); }; bool clauseFound = findRepeatableClause(callbackFn); diff --git a/flang/lib/Semantics/resolve-names.cpp b/flang/lib/Semantics/resolve-names.cpp index 2a487a6d39d51..0769ba4b64ebd 100644 --- a/flang/lib/Semantics/resolve-names.cpp +++ b/flang/lib/Semantics/resolve-names.cpp @@ -1631,6 +1631,8 @@ class OmpVisitor : public virtual DeclarationVisitor { return true; } bool Pre(const parser::OmpMapClause &); + bool Pre(const parser::OmpClause::To &); + bool Pre(const parser::OmpClause::From &); bool Pre(const parser::OpenMPSectionsConstruct &) { PushScope(Scope::Kind::OtherConstruct, nullptr); @@ -1777,6 +1779,7 @@ class OmpVisitor : public virtual DeclarationVisitor { } private: + void ResolveMapperModifier(parser::OmpMapper &mapper); void ProcessMapperSpecifier(const parser::OmpMapperSpecifier &spec, const parser::OmpClauseList &clauses); void ProcessReductionSpecifier(const parser::OmpReductionSpecifier &spec, @@ -1848,32 +1851,49 @@ void OmpVisitor::Post(const parser::OmpStylizedInstance &x) { // bool OmpVisitor::Pre(const parser::OmpMapClause &x) { auto &mods{OmpGetModifiers(x)}; if (auto *mapper{OmpGetUniqueModifier(mods)}) { - if (auto *symbol{FindSymbol(currScope(), mapper->v)}) { - // TODO: Do we need a specific flag or type here, to distinghuish against - // other ConstructName things? Leaving this for the full implementation - // of mapper lowering. - auto &ultimate{symbol->GetUltimate()}; - auto *misc{ultimate.detailsIf()}; - auto *md{ultimate.detailsIf()}; - if (!md && (!misc || misc->kind() != MiscDetails::Kind::ConstructName)) - context().Say(mapper->v.source, - "Name '%s' should be a mapper name"_err_en_US, mapper->v.source); - else - mapper->v.symbol = symbol; + ResolveMapperModifier(const_cast(*mapper)); + } + return true; +} + +bool OmpVisitor::Pre(const parser::OmpClause::To &x) { + auto &mods{OmpGetModifiers(x.v)}; + if (auto *mapper{OmpGetUniqueModifier(mods)}) { + ResolveMapperModifier(const_cast(*mapper)); + } + return true; +} + +bool OmpVisitor::Pre(const parser::OmpClause::From &x) { + auto &mods{OmpGetModifiers(x.v)}; + if (auto *mapper{OmpGetUniqueModifier(mods)}) { + ResolveMapperModifier(const_cast(*mapper)); + } + return true; +} + +void OmpVisitor::ResolveMapperModifier(parser::OmpMapper &mapper) { + if (auto *symbol{FindSymbol(currScope(), mapper.v)}) { + auto &ultimate{symbol->GetUltimate()}; + auto *misc{ultimate.detailsIf()}; + auto *md{ultimate.detailsIf()}; + if (!md && (!misc || misc->kind() != MiscDetails::Kind::ConstructName)) + context().Say(mapper.v.source, + "Name '%s' should be a mapper name"_err_en_US, mapper.v.source); + else + mapper.v.symbol = symbol; + } else { + // Allow the special 'default' mapper identifier without prior + // declaration so lowering can recognize and handle it. Emit an + // error for any other missing mapper identifier. + if (mapper.v.source.ToString() == "default") { + mapper.v.symbol = + &MakeSymbol(mapper.v, MiscDetails{MiscDetails::Kind::ConstructName}); } else { - // Allow the special 'default' mapper identifier without prior - // declaration so lowering can recognize and handle it. Emit an - // error for any other missing mapper identifier. - if (mapper->v.source.ToString() == "default") { - mapper->v.symbol = &MakeSymbol( - mapper->v, MiscDetails{MiscDetails::Kind::ConstructName}); - } else { - context().Say( - mapper->v.source, "'%s' not declared"_err_en_US, mapper->v.source); - } + context().Say( + mapper.v.source, "'%s' not declared"_err_en_US, mapper.v.source); } } - return true; } void OmpVisitor::ProcessMapperSpecifier(const parser::OmpMapperSpecifier &spec, @@ -2382,7 +2402,7 @@ void AttrsVisitor::SetBindNameOn(Symbol &symbol) { } symbol.SetBindName(std::move(*label)); if (!oldBindName.empty()) { - if (const std::string * newBindName{symbol.GetBindName()}) { + if (const std::string *newBindName{symbol.GetBindName()}) { if (oldBindName != *newBindName) { Say(symbol.name(), "The entity '%s' has multiple BIND names ('%s' and '%s')"_err_en_US, @@ -2508,7 +2528,7 @@ void DeclTypeSpecVisitor::Post(const parser::TypeSpec &typeSpec) { // expression semantics if the DeclTypeSpec is a valid TypeSpec. // The grammar ensures that it's an intrinsic or derived type spec, // not TYPE(*) or CLASS(*) or CLASS(T). - if (const DeclTypeSpec * spec{state_.declTypeSpec}) { + if (const DeclTypeSpec *spec{state_.declTypeSpec}) { switch (spec->category()) { case DeclTypeSpec::Numeric: case DeclTypeSpec::Logical: @@ -2516,7 +2536,7 @@ void DeclTypeSpecVisitor::Post(const parser::TypeSpec &typeSpec) { typeSpec.declTypeSpec = spec; break; case DeclTypeSpec::TypeDerived: - if (const DerivedTypeSpec * derived{spec->AsDerived()}) { + if (const DerivedTypeSpec *derived{spec->AsDerived()}) { CheckForAbstractType(derived->typeSymbol()); // C703 typeSpec.declTypeSpec = spec; } @@ -3107,8 +3127,8 @@ Symbol &ScopeHandler::MakeSymbol(const parser::Name &name, Attrs attrs) { Symbol &ScopeHandler::MakeHostAssocSymbol( const parser::Name &name, const Symbol &hostSymbol) { Symbol &symbol{*NonDerivedTypeScope() - .try_emplace(name.source, HostAssocDetails{hostSymbol}) - .first->second}; + .try_emplace(name.source, HostAssocDetails{hostSymbol}) + .first->second}; name.symbol = &symbol; symbol.attrs() = hostSymbol.attrs(); // TODO: except PRIVATE, PUBLIC? // These attributes can be redundantly reapplied without error @@ -3196,7 +3216,7 @@ void ScopeHandler::ApplyImplicitRules( if (context().HasError(symbol) || !NeedsType(symbol)) { return; } - if (const DeclTypeSpec * type{GetImplicitType(symbol)}) { + if (const DeclTypeSpec *type{GetImplicitType(symbol)}) { if (!skipImplicitTyping_) { symbol.set(Symbol::Flag::Implicit); symbol.SetType(*type); @@ -3296,7 +3316,7 @@ const DeclTypeSpec *ScopeHandler::GetImplicitType( const auto *type{implicitRulesMap_->at(scope).GetType( symbol.name(), respectImplicitNoneType)}; if (type) { - if (const DerivedTypeSpec * derived{type->AsDerived()}) { + if (const DerivedTypeSpec *derived{type->AsDerived()}) { // Resolve any forward-referenced derived type; a quick no-op else. auto &instantiatable{*const_cast(derived)}; instantiatable.Instantiate(currScope()); @@ -4316,7 +4336,7 @@ Scope *ModuleVisitor::FindModule(const parser::Name &name, if (scope) { if (DoesScopeContain(scope, currScope())) { // 14.2.2(1) std::optional submoduleName; - if (const Scope * container{FindModuleOrSubmoduleContaining(currScope())}; + if (const Scope *container{FindModuleOrSubmoduleContaining(currScope())}; container && container->IsSubmodule()) { submoduleName = container->GetName(); } @@ -4421,7 +4441,7 @@ bool InterfaceVisitor::isAbstract() const { void InterfaceVisitor::AddSpecificProcs( const std::list &names, ProcedureKind kind) { - if (Symbol * symbol{GetGenericInfo().symbol}; + if (Symbol *symbol{GetGenericInfo().symbol}; symbol && symbol->has()) { for (const auto &name : names) { specificsForGenericProcs_.emplace(symbol, std::make_pair(&name, kind)); @@ -4521,7 +4541,7 @@ void GenericHandler::DeclaredPossibleSpecificProc(Symbol &proc) { } void InterfaceVisitor::ResolveNewSpecifics() { - if (Symbol * generic{genericInfo_.top().symbol}; + if (Symbol *generic{genericInfo_.top().symbol}; generic && generic->has()) { ResolveSpecificsInGeneric(*generic, false); } @@ -4606,7 +4626,7 @@ bool SubprogramVisitor::HandleStmtFunction(const parser::StmtFunctionStmt &x) { name.source); MakeSymbol(name, Attrs{}, UnknownDetails{}); } else if (auto *entity{ultimate.detailsIf()}; - entity && !ultimate.has()) { + entity && !ultimate.has()) { resultType = entity->type(); ultimate.details() = UnknownDetails{}; // will be replaced below } else { @@ -4665,7 +4685,7 @@ bool SubprogramVisitor::Pre(const parser::Suffix &suffix) { } else { Message &msg{Say(*suffix.resultName, "RESULT(%s) may appear only in a function"_err_en_US)}; - if (const Symbol * subprogram{InclusiveScope().symbol()}) { + if (const Symbol *subprogram{InclusiveScope().symbol()}) { msg.Attach(subprogram->name(), "Containing subprogram"_en_US); } } @@ -5181,7 +5201,7 @@ Symbol *ScopeHandler::FindSeparateModuleProcedureInterface( symbol = generic->specific(); } } - if (const Symbol * defnIface{FindSeparateModuleSubprogramInterface(symbol)}) { + if (const Symbol *defnIface{FindSeparateModuleSubprogramInterface(symbol)}) { // Error recovery in case of multiple definitions symbol = const_cast(defnIface); } @@ -5320,8 +5340,8 @@ bool SubprogramVisitor::HandlePreviousCalls( return generic->specific() && HandlePreviousCalls(name, *generic->specific(), subpFlag); } else if (const auto *proc{symbol.detailsIf()}; proc && - !proc->isDummy() && - !symbol.attrs().HasAny(Attrs{Attr::INTRINSIC, Attr::POINTER})) { + !proc->isDummy() && + !symbol.attrs().HasAny(Attrs{Attr::INTRINSIC, Attr::POINTER})) { // There's a symbol created for previous calls to this subprogram or // ENTRY's name. We have to replace that symbol in situ to avoid the // obligation to rewrite symbol pointers in the parse tree. @@ -5363,7 +5383,7 @@ const Symbol *SubprogramVisitor::CheckExtantProc( if (prev) { if (IsDummy(*prev)) { } else if (auto *entity{prev->detailsIf()}; - IsPointer(*prev) && entity && !entity->type()) { + IsPointer(*prev) && entity && !entity->type()) { // POINTER attribute set before interface } else if (inInterfaceBlock() && currScope() != prev->owner()) { // Procedures in an INTERFACE block do not resolve to symbols @@ -5435,7 +5455,7 @@ Symbol *SubprogramVisitor::PushSubprogramScope(const parser::Name &name, } set_inheritFromParent(false); // interfaces don't inherit, even if MODULE } - if (Symbol * found{FindSymbol(name)}; + if (Symbol *found{FindSymbol(name)}; found && found->has()) { found->set(subpFlag); // PushScope() created symbol } @@ -6286,9 +6306,9 @@ void DeclarationVisitor::Post(const parser::VectorTypeSpec &x) { vectorDerivedType.CookParameters(GetFoldingContext()); } - if (const DeclTypeSpec * - extant{ppcBuiltinTypesScope->FindInstantiatedDerivedType( - vectorDerivedType, DeclTypeSpec::Category::TypeDerived)}) { + if (const DeclTypeSpec *extant{ + ppcBuiltinTypesScope->FindInstantiatedDerivedType( + vectorDerivedType, DeclTypeSpec::Category::TypeDerived)}) { // This derived type and parameter expressions (if any) are already present // in the __ppc_intrinsics scope. SetDeclTypeSpec(*extant); @@ -6310,7 +6330,7 @@ bool DeclarationVisitor::Pre(const parser::DeclarationTypeSpec::Type &) { void DeclarationVisitor::Post(const parser::DeclarationTypeSpec::Type &type) { const parser::Name &derivedName{std::get(type.derived.t)}; - if (const Symbol * derivedSymbol{derivedName.symbol}) { + if (const Symbol *derivedSymbol{derivedName.symbol}) { CheckForAbstractType(*derivedSymbol); // C706 } } @@ -6379,8 +6399,8 @@ void DeclarationVisitor::Post(const parser::DerivedTypeSpec &x) { if (!spec->MightBeParameterized()) { spec->EvaluateParameters(context()); } - if (const DeclTypeSpec * - extant{currScope().FindInstantiatedDerivedType(*spec, category)}) { + if (const DeclTypeSpec *extant{ + currScope().FindInstantiatedDerivedType(*spec, category)}) { // This derived type and parameter expressions (if any) are already present // in this scope. SetDeclTypeSpec(*extant); @@ -6411,8 +6431,7 @@ void DeclarationVisitor::Post(const parser::DeclarationTypeSpec::Record &rec) { if (auto spec{ResolveDerivedType(typeName)}) { spec->CookParameters(GetFoldingContext()); spec->EvaluateParameters(context()); - if (const DeclTypeSpec * - extant{currScope().FindInstantiatedDerivedType( + if (const DeclTypeSpec *extant{currScope().FindInstantiatedDerivedType( *spec, DeclTypeSpec::TypeDerived)}) { SetDeclTypeSpec(*extant); } else { @@ -7423,7 +7442,7 @@ bool DeclarationVisitor::PassesLocalityChecks( "Coarray '%s' not allowed in a %s locality-spec"_err_en_US, specName); return false; } - if (const DeclTypeSpec * type{symbol.GetType()}) { + if (const DeclTypeSpec *type{symbol.GetType()}) { if (type->IsPolymorphic() && IsDummy(symbol) && !IsPointer(symbol) && !isReduce) { // F'2023 C1130 SayWithDecl(name, symbol, @@ -7650,7 +7669,7 @@ Symbol *DeclarationVisitor::NoteInterfaceName(const parser::Name &name) { } void DeclarationVisitor::CheckExplicitInterface(const parser::Name &name) { - if (const Symbol * symbol{name.symbol}) { + if (const Symbol *symbol{name.symbol}) { const Symbol &ultimate{symbol->GetUltimate()}; if (!context().HasError(*symbol) && !context().HasError(ultimate) && !BypassGeneric(ultimate).HasExplicitInterface()) { @@ -7969,7 +7988,7 @@ bool ConstructVisitor::Pre(const parser::DataStmtValue &x) { auto &mutableData{const_cast(data)}; if (auto *elem{parser::Unwrap(mutableData)}) { if (const auto *name{std::get_if(&elem->base.u)}) { - if (const Symbol * symbol{FindSymbol(*name)}; + if (const Symbol *symbol{FindSymbol(*name)}; symbol && symbol->GetUltimate().has()) { mutableData.u = elem->ConvertToStructureConstructor( DerivedTypeSpec{name->source, *symbol}); @@ -8115,15 +8134,15 @@ void ConstructVisitor::Post(const parser::SelectTypeStmt &x) { } } } else { - if (const Symbol * - whole{UnwrapWholeSymbolDataRef(association.selector.expr)}) { + if (const Symbol *whole{ + UnwrapWholeSymbolDataRef(association.selector.expr)}) { ConvertToObjectEntity(const_cast(*whole)); if (!IsVariableName(*whole)) { Say(association.selector.source, // C901 "Selector is not a variable"_err_en_US); association = {}; } - if (const DeclTypeSpec * type{whole->GetType()}) { + if (const DeclTypeSpec *type{whole->GetType()}) { if (!type->IsPolymorphic()) { // C1159 Say(association.selector.source, "Selector '%s' in SELECT TYPE statement must be " @@ -8263,8 +8282,8 @@ Symbol *ConstructVisitor::MakeAssocEntity() { "The associate name '%s' is already used in this associate statement"_err_en_US); return nullptr; } - } else if (const Symbol * - whole{UnwrapWholeSymbolDataRef(association.selector.expr)}) { + } else if (const Symbol *whole{ + UnwrapWholeSymbolDataRef(association.selector.expr)}) { symbol = &MakeSymbol(whole->name()); } else { return nullptr; @@ -8884,7 +8903,7 @@ bool DeclarationVisitor::CheckForHostAssociatedImplicit( if (name.symbol) { ApplyImplicitRules(*name.symbol, true); } - if (Scope * host{GetHostProcedure()}; host && !isImplicitNoneType(*host)) { + if (Scope *host{GetHostProcedure()}; host && !isImplicitNoneType(*host)) { Symbol *hostSymbol{nullptr}; if (!name.symbol) { if (currScope().CanImport(name.source)) { @@ -8955,7 +8974,7 @@ const parser::Name *DeclarationVisitor::FindComponent( if (!type) { return nullptr; // should have already reported error } - if (const IntrinsicTypeSpec * intrinsic{type->AsIntrinsic()}) { + if (const IntrinsicTypeSpec *intrinsic{type->AsIntrinsic()}) { auto category{intrinsic->category()}; MiscDetails::Kind miscKind{MiscDetails::Kind::None}; if (component.source == "kind") { @@ -8977,7 +8996,7 @@ const parser::Name *DeclarationVisitor::FindComponent( } } else if (DerivedTypeSpec * derived{type->AsDerived()}) { derived->Instantiate(currScope()); // in case of forward referenced type - if (const Scope * scope{derived->scope()}) { + if (const Scope *scope{derived->scope()}) { if (Resolve(component, scope->FindComponent(component.source))) { if (auto msg{CheckAccessibleSymbol(currScope(), *component.symbol)}) { context().Say(component.source, *msg); @@ -9128,8 +9147,8 @@ void DeclarationVisitor::PointerInitialization( if (evaluate::IsNullProcedurePointer(&*expr)) { CHECK(!details->init()); details->set_init(nullptr); - } else if (const Symbol * - targetSymbol{evaluate::UnwrapWholeSymbolDataRef(*expr)}) { + } else if (const Symbol *targetSymbol{ + evaluate::UnwrapWholeSymbolDataRef(*expr)}) { CHECK(!details->init()); details->set_init(*targetSymbol); } else { @@ -9703,7 +9722,7 @@ void ResolveNamesVisitor::EarlyDummyTypeDeclaration( for (const auto &ent : entities) { const auto &objName{std::get(ent.t)}; Resolve(objName, FindInScope(currScope(), objName)); - if (Symbol * symbol{objName.symbol}; + if (Symbol *symbol{objName.symbol}; symbol && IsDummy(*symbol) && NeedsType(*symbol)) { if (!type) { type = ProcessTypeSpec(declTypeSpec); @@ -9842,7 +9861,7 @@ void ResolveNamesVisitor::FinishSpecificationPart( if (auto *proc{symbol.detailsIf()}; proc && !proc->isDummy() && !IsPointer(symbol) && !symbol.attrs().test(Attr::BIND_C)) { - if (const Symbol * iface{proc->procInterface()}; + if (const Symbol *iface{proc->procInterface()}; iface && IsBindCProcedure(*iface)) { SetImplicitAttr(symbol, Attr::BIND_C); SetBindNameOn(symbol); @@ -9975,7 +9994,7 @@ bool ResolveNamesVisitor::Pre(const parser::PointerAssignmentStmt &x) { Symbol *ptrSymbol{parser::GetLastName(dataRef).symbol}; Walk(bounds); // Resolve unrestricted specific intrinsic procedures as in "p => cos". - if (const parser::Name * name{parser::Unwrap(expr)}) { + if (const parser::Name *name{parser::Unwrap(expr)}) { if (NameIsKnownOrIntrinsic(*name)) { if (Symbol * symbol{name->symbol}) { if (IsProcedurePointer(ptrSymbol) && @@ -10424,8 +10443,8 @@ void ResolveNamesVisitor::ResolveSpecificationParts(ProgramTree &node) { // implied SAVE so that evaluate::IsSaved() will return true. if (node.scope()->kind() == Scope::Kind::MainProgram) { if (const auto *object{symbol.detailsIf()}) { - if (const DeclTypeSpec * type{object->type()}) { - if (const DerivedTypeSpec * derived{type->AsDerived()}) { + if (const DeclTypeSpec *type{object->type()}) { + if (const DerivedTypeSpec *derived{type->AsDerived()}) { if (!IsSaved(symbol) && FindCoarrayPotentialComponent(*derived)) { SetImplicitAttr(symbol, Attr::SAVE); } @@ -10682,7 +10701,7 @@ void ResolveNamesVisitor::FinishDerivedTypeInstantiation(Scope &scope) { if (DerivedTypeSpec * spec{scope.derivedTypeSpec()}) { spec->Instantiate(currScope()); const Symbol &origTypeSymbol{spec->typeSymbol()}; - if (const Scope * origTypeScope{origTypeSymbol.scope()}) { + if (const Scope *origTypeScope{origTypeSymbol.scope()}) { CHECK(origTypeScope->IsDerivedType() && origTypeScope->symbol() == &origTypeSymbol); auto &foldingContext{GetFoldingContext()}; @@ -10693,7 +10712,7 @@ void ResolveNamesVisitor::FinishDerivedTypeInstantiation(Scope &scope) { if (IsPointer(comp)) { if (auto *details{comp.detailsIf()}) { auto origDetails{origComp.get()}; - if (const MaybeExpr & init{origDetails.init()}) { + if (const MaybeExpr &init{origDetails.init()}) { SomeExpr newInit{*init}; MaybeExpr folded{FoldExpr(std::move(newInit))}; details->set_init(std::move(folded)); diff --git a/flang/test/Lower/OpenMP/declare-mapper.f90 b/flang/test/Lower/OpenMP/declare-mapper.f90 index 7eda1a4c497be..18de556e2ce7d 100644 --- a/flang/test/Lower/OpenMP/declare-mapper.f90 +++ b/flang/test/Lower/OpenMP/declare-mapper.f90 @@ -11,6 +11,7 @@ ! RUN: %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=50 -J %t %t/omp-declare-mapper-7.use.f90 -o - | FileCheck %t/omp-declare-mapper-7.use.f90 ! RUN: %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=50 -module-dir %t %t/omp-declare-mapper-8.mod.f90 -o - >/dev/null ! RUN: %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=50 -J %t %t/omp-declare-mapper-8.use.f90 -o - | FileCheck %t/omp-declare-mapper-8.use.f90 +! RUN: %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=52 %t/omp-declare-mapper-9.f90 -o - | FileCheck %t/omp-declare-mapper-9.f90 !--- omp-declare-mapper-1.f90 subroutine declare_mapper_1 @@ -360,3 +361,36 @@ program use_module_default_mapper a%x = 8 !$omp end target end program use_module_default_mapper + +!--- omp-declare-mapper-9.f90 +! Test mapper usage in target update to/from clauses +program target_update_mapper + type :: typ + integer :: a + integer :: b + end type typ + + !CHECK: omp.declare_mapper @_QQFcustom : !fir.type<_QFTtyp{a:i32,b:i32}> + !CHECK: omp.declare_mapper @_QQFtyp_omp_default_mapper : !fir.type<_QFTtyp{a:i32,b:i32}> + + !$omp declare mapper(typ :: t) map(t%a, t%b) + !$omp declare mapper(custom: typ :: t) map(t%a) + + type(typ) :: t + + ! Test target update to with custom mapper + !CHECK: %[[MAP_INFO:.*]] = omp.map.info var_ptr(%{{.*}} : {{.*}}, {{.*}}) map_clauses(to) capture(ByRef) mapper(@_QQFcustom) -> {{.*}} + !CHECK: omp.target_update map_entries(%[[MAP_INFO]] : {{.*}}) + !$omp target update to(mapper(custom): t) + + ! Test target update from with custom mapper + !CHECK: %[[MAP_INFO2:.*]] = omp.map.info var_ptr(%{{.*}} : {{.*}}, {{.*}}) map_clauses(from) capture(ByRef) mapper(@_QQFcustom) -> {{.*}} + !CHECK: omp.target_update map_entries(%[[MAP_INFO2]] : {{.*}}) + !$omp target update from(mapper(custom): t) + + ! Test target update to with default mapper + !CHECK: %[[MAP_INFO3:.*]] = omp.map.info var_ptr(%{{.*}} : {{.*}}, {{.*}}) map_clauses(to) capture(ByRef) mapper(@_QQFtyp_omp_default_mapper) -> {{.*}} + !CHECK: omp.target_update map_entries(%[[MAP_INFO3]] : {{.*}}) + !$omp target update to(mapper(default): t) + +end program target_update_mapper diff --git a/flang/test/Semantics/OpenMP/target-update-mapper.f90 b/flang/test/Semantics/OpenMP/target-update-mapper.f90 new file mode 100644 index 0000000000000..f37d288670594 --- /dev/null +++ b/flang/test/Semantics/OpenMP/target-update-mapper.f90 @@ -0,0 +1,30 @@ +! RUN: %python %S/../test_errors.py %s %flang -fopenmp -fopenmp-version=52 + +! Test mapper name resolution in target update to/from clauses + +program target_update_mapper + type :: typ + integer :: a + end type typ + + !$omp declare mapper(custom: typ :: t) map(t%a) + + type(typ) :: t + integer :: not_a_mapper + + ! Valid: using custom mapper + !$omp target update to(mapper(custom): t) + !$omp target update from(mapper(custom): t) + + ! Valid: using default mapper + !$omp target update to(mapper(default): t) + + ! Error: undefined mapper + !ERROR: 'undefined_mapper' not declared + !$omp target update to(mapper(undefined_mapper): t) + + ! Error: wrong kind of symbol + !ERROR: Name 'not_a_mapper' should be a mapper name + !$omp target update from(mapper(not_a_mapper): t) + +end program target_update_mapper