Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 2 additions & 0 deletions flang/include/flang/Parser/dump-parse-tree.h
Original file line number Diff line number Diff line change
Expand Up @@ -520,6 +520,8 @@ class ParseTreeDumper {
NODE(parser, OmpAtClause)
NODE_ENUM(OmpAtClause, ActionTime)
NODE(parser, OmpAtomicDefaultMemOrderClause)
NODE(parser, OmpAttachModifier)
NODE_ENUM(OmpAttachModifier, Value)
NODE(parser, OmpAutomapModifier)
NODE_ENUM(OmpAutomapModifier, Value)
NODE(parser, OmpBaseVariantNames)
Expand Down
19 changes: 16 additions & 3 deletions flang/include/flang/Parser/parse-tree.h
Original file line number Diff line number Diff line change
Expand Up @@ -3813,6 +3813,18 @@ struct OmpAlwaysModifier {
WRAPPER_CLASS_BOILERPLATE(OmpAlwaysModifier, Value);
};

// Ref: [coming in 6.1]
//
// attach-modifier ->
// ATTACH(attachment-mode) // since 6.1
//
// attachment-mode ->
// ALWAYS | AUTO | NEVER
struct OmpAttachModifier {
ENUM_CLASS(Value, Always, Never, Auto)
WRAPPER_CLASS_BOILERPLATE(OmpAttachModifier, Value);
};

// Ref: [6.0:289-290]
//
// automap-modifier ->
Expand Down Expand Up @@ -4575,6 +4587,7 @@ struct OmpLoopRangeClause {
// modifier ->
// map-type-modifier [replaced] | // since 4.5, until 5.2
// always-modifier | // since 6.0
// attach-modifier | // since 6.1
// close-modifier | // since 6.0
// delete-modifier | // since 6.0
// present-modifier | // since 6.0
Expand All @@ -4589,9 +4602,9 @@ struct OmpLoopRangeClause {
// and delete-modifier has been split from map-type.
struct OmpMapClause {
TUPLE_CLASS_BOILERPLATE(OmpMapClause);
MODIFIER_BOILERPLATE(OmpAlwaysModifier, OmpCloseModifier, OmpDeleteModifier,
OmpMapTypeModifier, OmpPresentModifier, OmpRefModifier, OmpSelfModifier,
OmpMapper, OmpIterator, OmpMapType, OmpxHoldModifier);
MODIFIER_BOILERPLATE(OmpAlwaysModifier, OmpAttachModifier, OmpCloseModifier,
OmpDeleteModifier, OmpMapTypeModifier, OmpPresentModifier, OmpRefModifier,
OmpSelfModifier, OmpMapper, OmpIterator, OmpMapType, OmpxHoldModifier);
std::tuple<MODIFIERS(), OmpObjectList, /*CommaSeparated=*/bool> t;
};

Expand Down
1 change: 1 addition & 0 deletions flang/include/flang/Semantics/openmp-modifiers.h
Original file line number Diff line number Diff line change
Expand Up @@ -72,6 +72,7 @@ DECLARE_DESCRIPTOR(parser::OmpAlignModifier);
DECLARE_DESCRIPTOR(parser::OmpAllocatorComplexModifier);
DECLARE_DESCRIPTOR(parser::OmpAllocatorSimpleModifier);
DECLARE_DESCRIPTOR(parser::OmpAlwaysModifier);
DECLARE_DESCRIPTOR(parser::OmpAttachModifier);
DECLARE_DESCRIPTOR(parser::OmpAutomapModifier);
DECLARE_DESCRIPTOR(parser::OmpChunkModifier);
DECLARE_DESCRIPTOR(parser::OmpCloseModifier);
Expand Down
6 changes: 4 additions & 2 deletions flang/lib/Lower/OpenMP/ClauseProcessor.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -1343,8 +1343,10 @@ bool ClauseProcessor::processMap(
const parser::CharBlock &source) {
using Map = omp::clause::Map;
mlir::Location clauseLocation = converter.genLocation(source);
const auto &[mapType, typeMods, refMod, mappers, iterator, objects] =
clause.t;
const auto &[mapType, typeMods, attachMod, refMod, mappers, iterator,
objects] = clause.t;
if (attachMod)
TODO(currentLocation, "ATTACH modifier is not implemented yet");
llvm::omp::OpenMPOffloadMappingFlags mapTypeBits =
llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_NONE;
std::string mapperIdName = "__implicit_mapper";
Expand Down
17 changes: 17 additions & 0 deletions flang/lib/Lower/OpenMP/Clauses.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -1068,6 +1068,15 @@ Map make(const parser::OmpClause::Map &inp,
// clang-format on
);

CLAUSET_ENUM_CONVERT( //
convertAttachMod, parser::OmpAttachModifier::Value, Map::AttachModifier,
// clang-format off
MS(Always, Always)
MS(Auto, Auto)
MS(Never, Never)
// clang-format on
);

CLAUSET_ENUM_CONVERT( //
convertRefMod, parser::OmpRefModifier::Value, Map::RefModifier,
// clang-format off
Expand Down Expand Up @@ -1115,6 +1124,13 @@ Map make(const parser::OmpClause::Map &inp,
if (!modSet.empty())
maybeTypeMods = Map::MapTypeModifiers(modSet.begin(), modSet.end());

auto attachMod = [&]() -> std::optional<Map::AttachModifier> {
if (auto *t =
semantics::OmpGetUniqueModifier<parser::OmpAttachModifier>(mods))
return convertAttachMod(t->v);
return std::nullopt;
}();

auto refMod = [&]() -> std::optional<Map::RefModifier> {
if (auto *t = semantics::OmpGetUniqueModifier<parser::OmpRefModifier>(mods))
return convertRefMod(t->v);
Expand All @@ -1135,6 +1151,7 @@ Map make(const parser::OmpClause::Map &inp,

return Map{{/*MapType=*/std::move(type),
/*MapTypeModifiers=*/std::move(maybeTypeMods),
/*AttachModifier=*/std::move(attachMod),
/*RefModifier=*/std::move(refMod), /*Mapper=*/std::move(mappers),
/*Iterator=*/std::move(iterator),
/*LocatorList=*/makeObjects(t2, semaCtx)}};
Expand Down
9 changes: 9 additions & 0 deletions flang/lib/Parser/openmp-parsers.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -548,6 +548,14 @@ TYPE_PARSER(construct<OmpAllocatorSimpleModifier>(scalarIntExpr))
TYPE_PARSER(construct<OmpAlwaysModifier>( //
"ALWAYS" >> pure(OmpAlwaysModifier::Value::Always)))

TYPE_PARSER(construct<OmpAttachModifier::Value>(
"ALWAYS" >> pure(OmpAttachModifier::Value::Always) ||
"AUTO" >> pure(OmpAttachModifier::Value::Auto) ||
"NEVER" >> pure(OmpAttachModifier::Value::Never)))

TYPE_PARSER(construct<OmpAttachModifier>( //
"ATTACH" >> parenthesized(Parser<OmpAttachModifier::Value>{})))

TYPE_PARSER(construct<OmpAutomapModifier>(
"AUTOMAP" >> pure(OmpAutomapModifier::Value::Automap)))

Expand Down Expand Up @@ -744,6 +752,7 @@ TYPE_PARSER(sourced(

TYPE_PARSER(sourced(construct<OmpMapClause::Modifier>(
sourced(construct<OmpMapClause::Modifier>(Parser<OmpAlwaysModifier>{}) ||
construct<OmpMapClause::Modifier>(Parser<OmpAttachModifier>{}) ||
construct<OmpMapClause::Modifier>(Parser<OmpCloseModifier>{}) ||
construct<OmpMapClause::Modifier>(Parser<OmpDeleteModifier>{}) ||
construct<OmpMapClause::Modifier>(Parser<OmpPresentModifier>{}) ||
Expand Down
6 changes: 6 additions & 0 deletions flang/lib/Parser/unparse.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -2384,6 +2384,11 @@ class UnparseVisitor {
Walk(x.v);
Put(")");
}
void Unparse(const OmpAttachModifier &x) {
Word("ATTACH(");
Walk(x.v);
Put(")");
}
void Unparse(const OmpOrderClause &x) {
using Modifier = OmpOrderClause::Modifier;
Walk(std::get<std::optional<std::list<Modifier>>>(x.t), ":");
Expand Down Expand Up @@ -2820,6 +2825,7 @@ class UnparseVisitor {
WALK_NESTED_ENUM(OmpMapType, Value) // OMP map-type
WALK_NESTED_ENUM(OmpMapTypeModifier, Value) // OMP map-type-modifier
WALK_NESTED_ENUM(OmpAlwaysModifier, Value)
WALK_NESTED_ENUM(OmpAttachModifier, Value)
WALK_NESTED_ENUM(OmpCloseModifier, Value)
WALK_NESTED_ENUM(OmpDeleteModifier, Value)
WALK_NESTED_ENUM(OmpPresentModifier, Value)
Expand Down
49 changes: 44 additions & 5 deletions flang/lib/Semantics/check-omp-structure.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -4081,9 +4081,15 @@ void OmpStructureChecker::Enter(const parser::OmpClause::Map &x) {
if (auto *iter{OmpGetUniqueModifier<parser::OmpIterator>(modifiers)}) {
CheckIteratorModifier(*iter);
}

using Directive = llvm::omp::Directive;
Directive dir{GetContext().directive};
llvm::ArrayRef<Directive> leafs{llvm::omp::getLeafConstructsOrSelf(dir)};
parser::OmpMapType::Value mapType{parser::OmpMapType::Value::Storage};

if (auto *type{OmpGetUniqueModifier<parser::OmpMapType>(modifiers)}) {
using Directive = llvm::omp::Directive;
using Value = parser::OmpMapType::Value;
mapType = type->v;

static auto isValidForVersion{
[](parser::OmpMapType::Value t, unsigned version) {
Expand Down Expand Up @@ -4120,10 +4126,6 @@ void OmpStructureChecker::Enter(const parser::OmpClause::Map &x) {
return result;
}()};

llvm::omp::Directive dir{GetContext().directive};
llvm::ArrayRef<llvm::omp::Directive> leafs{
llvm::omp::getLeafConstructsOrSelf(dir)};

if (llvm::is_contained(leafs, Directive::OMPD_target) ||
llvm::is_contained(leafs, Directive::OMPD_target_data)) {
if (version >= 60) {
Expand All @@ -4141,6 +4143,43 @@ void OmpStructureChecker::Enter(const parser::OmpClause::Map &x) {
}
}

if (auto *attach{
OmpGetUniqueModifier<parser::OmpAttachModifier>(modifiers)}) {
bool mapEnteringConstructOrMapper{
llvm::is_contained(leafs, Directive::OMPD_target) ||
llvm::is_contained(leafs, Directive::OMPD_target_data) ||
llvm::is_contained(leafs, Directive::OMPD_target_enter_data) ||
llvm::is_contained(leafs, Directive::OMPD_declare_mapper)};

if (!mapEnteringConstructOrMapper || !IsMapEnteringType(mapType)) {
const auto &desc{OmpGetDescriptor<parser::OmpAttachModifier>()};
context_.Say(OmpGetModifierSource(modifiers, attach),
"The '%s' modifier can only appear on a map-entering construct or on a DECLARE_MAPPER directive"_err_en_US,
desc.name.str());
}

auto hasBasePointer{[&](const SomeExpr &item) {
evaluate::SymbolVector symbols{evaluate::GetSymbolVector(item)};
return llvm::any_of(
symbols, [](SymbolRef s) { return IsPointer(s.get()); });
}};

evaluate::ExpressionAnalyzer ea{context_};
const auto &objects{std::get<parser::OmpObjectList>(x.v.t)};
for (auto &object : objects.v) {
if (const parser::Designator *d{GetDesignatorFromObj(object)}) {
if (auto &&expr{ea.Analyze(*d)}) {
if (hasBasePointer(*expr)) {
continue;
}
}
}
auto source{GetObjectSource(object)};
context_.Say(source ? *source : GetContext().clauseSource,
"A list-item that appears in a map clause with the ATTACH modifier must have a base-pointer"_err_en_US);
}
}

auto &&typeMods{
OmpGetRepeatableModifier<parser::OmpMapTypeModifier>(modifiers)};
struct Less {
Expand Down
16 changes: 16 additions & 0 deletions flang/lib/Semantics/openmp-modifiers.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -156,6 +156,22 @@ const OmpModifierDescriptor &OmpGetDescriptor<parser::OmpAlwaysModifier>() {
return desc;
}

template <>
const OmpModifierDescriptor &OmpGetDescriptor<parser::OmpAttachModifier>() {
static const OmpModifierDescriptor desc{
/*name=*/"attach-modifier",
/*props=*/
{
{61, {OmpProperty::Unique}},
},
/*clauses=*/
{
{61, {Clause::OMPC_map}},
},
};
return desc;
}

template <>
const OmpModifierDescriptor &OmpGetDescriptor<parser::OmpAutomapModifier>() {
static const OmpModifierDescriptor desc{
Expand Down
9 changes: 9 additions & 0 deletions flang/test/Lower/OpenMP/Todo/attach-modifier.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
!RUN: %not_todo_cmd bbc -emit-hlfir -fopenmp -fopenmp-version=61 -o - %s 2>&1 | FileCheck %s
!RUN: %not_todo_cmd %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=61 -o - %s 2>&1 | FileCheck %s

!CHECK: not yet implemented: ATTACH modifier is not implemented yet
subroutine f00(x)
integer, pointer :: x
!$omp target map(attach(always), tofrom: x)
!$omp end target
end
64 changes: 64 additions & 0 deletions flang/test/Parser/OpenMP/map-modifiers-v61.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,64 @@
!RUN: %flang_fc1 -fdebug-unparse-no-sema -fopenmp -fopenmp-version=61 %s | FileCheck --ignore-case --check-prefix="UNPARSE" %s
!RUN: %flang_fc1 -fdebug-dump-parse-tree-no-sema -fopenmp -fopenmp-version=61 %s | FileCheck --check-prefix="PARSE-TREE" %s

subroutine f00(x)
integer, pointer :: x
!$omp target map(attach(always): x)
!$omp end target
end

!UNPARSE: SUBROUTINE f00 (x)
!UNPARSE: INTEGER, POINTER :: x
!UNPARSE: !$OMP TARGET MAP(ATTACH(ALWAYS): x)
!UNPARSE: !$OMP END TARGET
!UNPARSE: END SUBROUTINE

!PARSE-TREE: OmpBeginDirective
!PARSE-TREE: | OmpDirectiveName -> llvm::omp::Directive = target
!PARSE-TREE: | OmpClauseList -> OmpClause -> Map -> OmpMapClause
!PARSE-TREE: | | Modifier -> OmpAttachModifier -> Value = Always
!PARSE-TREE: | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
!PARSE-TREE: | | bool = 'true'
!PARSE-TREE: | Flags = None


subroutine f01(x)
integer, pointer :: x
!$omp target map(attach(auto): x)
!$omp end target
end

!UNPARSE: SUBROUTINE f01 (x)
!UNPARSE: INTEGER, POINTER :: x
!UNPARSE: !$OMP TARGET MAP(ATTACH(AUTO): x)
!UNPARSE: !$OMP END TARGET
!UNPARSE: END SUBROUTINE

!PARSE-TREE: OmpBeginDirective
!PARSE-TREE: | OmpDirectiveName -> llvm::omp::Directive = target
!PARSE-TREE: | OmpClauseList -> OmpClause -> Map -> OmpMapClause
!PARSE-TREE: | | Modifier -> OmpAttachModifier -> Value = Auto
!PARSE-TREE: | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
!PARSE-TREE: | | bool = 'true'
!PARSE-TREE: | Flags = None


subroutine f02(x)
integer, pointer :: x
!$omp target map(attach(never): x)
!$omp end target
end

!UNPARSE: SUBROUTINE f02 (x)
!UNPARSE: INTEGER, POINTER :: x
!UNPARSE: !$OMP TARGET MAP(ATTACH(NEVER): x)
!UNPARSE: !$OMP END TARGET
!UNPARSE: END SUBROUTINE

!PARSE-TREE: OmpBeginDirective
!PARSE-TREE: | OmpDirectiveName -> llvm::omp::Directive = target
!PARSE-TREE: | OmpClauseList -> OmpClause -> Map -> OmpMapClause
!PARSE-TREE: | | Modifier -> OmpAttachModifier -> Value = Never
!PARSE-TREE: | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
!PARSE-TREE: | | bool = 'true'
!PARSE-TREE: | Flags = None
49 changes: 49 additions & 0 deletions flang/test/Semantics/OpenMP/map-modifiers-v61.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,49 @@
!RUN: %python %S/../test_errors.py %s %flang -fopenmp -fopenmp-version=61 -Werror

subroutine f00(x)
integer, pointer :: x
!ERROR: 'attach-modifier' modifier cannot occur multiple times
!$omp target map(attach(always), attach(never): x)
!$omp end target
end

subroutine f01(x)
integer, pointer :: x
!ERROR: The 'attach-modifier' modifier can only appear on a map-entering construct or on a DECLARE_MAPPER directive
!$omp target_exit_data map(attach(always): x)
end

subroutine f02(x)
integer, pointer :: x
!ERROR: The 'attach-modifier' modifier can only appear on a map-entering construct or on a DECLARE_MAPPER directive
!$omp target map(attach(never), from: x)
!$omp end target
end

subroutine f03(x)
integer :: x
!ERROR: A list-item that appears in a map clause with the ATTACH modifier must have a base-pointer
!$omp target map(attach(always), tofrom: x)
!$omp end target
end

module m
type t
integer :: z
end type

type u
type(t), pointer :: y
end type

contains

subroutine f04(n)
integer :: n
type(u) :: x(10)

!Expect no diagonstics
!$omp target map(attach(always), to: x(n)%y%z)
!$omp end target
end
end module
5 changes: 3 additions & 2 deletions llvm/include/llvm/Frontend/OpenMP/ClauseT.h
Original file line number Diff line number Diff line change
Expand Up @@ -802,6 +802,7 @@ template <typename T, typename I, typename E> //
struct MapT {
using LocatorList = ObjectListT<I, E>;
ENUM(MapType, To, From, Tofrom, Storage);
ENUM(AttachModifier, Always, Auto, Never);
ENUM(MapTypeModifier, Always, Close, Delete, Present, Self, OmpxHold);
ENUM(RefModifier, RefPtee, RefPtr, RefPtrPtee);
// See note at the definition of the MapperT type.
Expand All @@ -810,8 +811,8 @@ struct MapT {
using MapTypeModifiers = ListT<MapTypeModifier>; // Not a spec name

using TupleTrait = std::true_type;
std::tuple<OPT(MapType), OPT(MapTypeModifiers), OPT(RefModifier),
OPT(Mappers), OPT(Iterator), LocatorList>
std::tuple<OPT(MapType), OPT(MapTypeModifiers), OPT(AttachModifier),
OPT(RefModifier), OPT(Mappers), OPT(Iterator), LocatorList>
t;
};

Expand Down
Loading