Revert "Revert "[flang][openmp] Adds Parser and Semantic Support for Interop Construct, and Init and Use Clauses."" (#132343)

Reverts llvm/llvm-project#132005
This commit is contained in:
swatheesh-mcw 2025-03-28 20:51:52 +05:30 committed by GitHub
parent 2218587b5b
commit fe30cf18ab
No known key found for this signature in database
GPG Key ID: B5690EEEBB952194
14 changed files with 525 additions and 2 deletions

View File

@ -522,6 +522,13 @@ public:
READ_FEATURE(OmpScheduleClause)
READ_FEATURE(OmpScheduleClause::Kind)
READ_FEATURE(OmpScheduleClause::Modifier)
READ_FEATURE(OmpInteropRuntimeIdentifier)
READ_FEATURE(OmpInteropPreference)
READ_FEATURE(OmpInteropType)
READ_FEATURE(OmpInteropType::Value)
READ_FEATURE(OmpInitClause)
READ_FEATURE(OmpInitClause::Modifier)
READ_FEATURE(OmpUseClause)
READ_FEATURE(OmpDeviceModifier)
READ_FEATURE(OmpDeviceClause)
READ_FEATURE(OmpDeviceClause::Modifier)
@ -541,6 +548,7 @@ public:
READ_FEATURE(OpenACCConstruct)
READ_FEATURE(OpenACCDeclarativeConstruct)
READ_FEATURE(OpenACCLoopConstruct)
READ_FEATURE(OpenMPInteropConstruct)
READ_FEATURE(OpenACCRoutineConstruct)
READ_FEATURE(OpenACCStandaloneDeclarativeConstruct)
READ_FEATURE(OpenACCStandaloneConstruct)

View File

@ -657,6 +657,13 @@ public:
NODE_ENUM(OmpDeviceModifier, Value)
NODE(parser, OmpDeviceTypeClause)
NODE_ENUM(OmpDeviceTypeClause, DeviceTypeDescription)
NODE(parser, OmpInteropRuntimeIdentifier)
NODE(parser, OmpInteropPreference)
NODE(parser, OmpInteropType)
NODE_ENUM(OmpInteropType, Value)
NODE(parser, OmpInitClause)
NODE(OmpInitClause, Modifier)
NODE(parser, OmpUseClause)
NODE(parser, OmpUpdateClause)
NODE(parser, OmpChunkModifier)
NODE_ENUM(OmpChunkModifier, Value)
@ -675,6 +682,7 @@ public:
NODE(parser, OpenACCDeclarativeConstruct)
NODE(parser, OpenACCEndConstruct)
NODE(parser, OpenACCLoopConstruct)
NODE(parser, OpenMPInteropConstruct)
NODE(parser, OpenACCRoutineConstruct)
NODE(parser, OpenACCStandaloneDeclarativeConstruct)
NODE(parser, OpenACCStandaloneConstruct)

View File

@ -3829,6 +3829,33 @@ struct OmpExpectation {
WRAPPER_CLASS_BOILERPLATE(OmpExpectation, Value);
};
// REF: [5.1:217-220], [5.2:293-294]
//
// OmpInteropRuntimeIdentifier -> // since 5.2
// CharLiteralConstant || ScalarIntConstantExpr
struct OmpInteropRuntimeIdentifier {
UNION_CLASS_BOILERPLATE(OmpInteropRuntimeIdentifier);
std::variant<CharLiteralConstant, ScalarIntConstantExpr> u;
};
// REF: [5.1:217-220], [5.2:293-294]
//
// OmpInteropPreference -> // since 5.2
// ([OmpRuntimeIdentifier, ...])
struct OmpInteropPreference {
WRAPPER_CLASS_BOILERPLATE(
OmpInteropPreference, std::list<OmpInteropRuntimeIdentifier>);
};
// REF: [5.1:217-220], [5.2:293-294]
//
// InteropType -> target || targetsync // since 5.2
// There can be at most only two interop-type.
struct OmpInteropType {
ENUM_CLASS(Value, Target, TargetSync)
WRAPPER_CLASS_BOILERPLATE(OmpInteropType, Value);
};
// Ref: [5.0:47-49], [5.1:49-51], [5.2:67-69]
//
// iterator-modifier ->
@ -4486,6 +4513,25 @@ struct OmpWhenClause {
t;
};
// REF: [5.1:217-220], [5.2:293-294]
//
// init-clause -> INIT ([interop-modifier,] [interop-type,]
// interop-type: interop-var)
// interop-modifier: prefer_type(preference-list)
// interop-type: target, targetsync
// interop-var: Ompobject
// There can be at most only two interop-type.
struct OmpInitClause {
TUPLE_CLASS_BOILERPLATE(OmpInitClause);
MODIFIER_BOILERPLATE(OmpInteropPreference, OmpInteropType);
std::tuple<MODIFIERS(), OmpObject> t;
};
// REF: [5.1:217-220], [5.2:294]
//
// 14.1.3 use-clause -> USE (interop-var)
WRAPPER_CLASS(OmpUseClause, OmpObject);
// OpenMP Clauses
struct OmpClause {
UNION_CLASS_BOILERPLATE(OmpClause);
@ -4935,6 +4981,14 @@ struct OpenMPFlushConstruct {
CharBlock source;
};
// Ref: [5.1:217-220], [5.2:291-292]
//
// interop -> INTEROP clause[ [ [,] clause]...]
struct OpenMPInteropConstruct {
WRAPPER_CLASS_BOILERPLATE(OpenMPInteropConstruct, OmpDirectiveSpecification);
CharBlock source;
};
struct OpenMPSimpleStandaloneConstruct {
WRAPPER_CLASS_BOILERPLATE(
OpenMPSimpleStandaloneConstruct, OmpDirectiveSpecification);
@ -4946,7 +5000,7 @@ struct OpenMPStandaloneConstruct {
CharBlock source;
std::variant<OpenMPSimpleStandaloneConstruct, OpenMPFlushConstruct,
OpenMPCancelConstruct, OpenMPCancellationPointConstruct,
OpenMPDepobjConstruct, OmpMetadirectiveDirective>
OpenMPDepobjConstruct, OmpMetadirectiveDirective, OpenMPInteropConstruct>
u;
};

View File

@ -77,6 +77,8 @@ DECLARE_DESCRIPTOR(parser::OmpDependenceType);
DECLARE_DESCRIPTOR(parser::OmpDeviceModifier);
DECLARE_DESCRIPTOR(parser::OmpDirectiveNameModifier);
DECLARE_DESCRIPTOR(parser::OmpExpectation);
DECLARE_DESCRIPTOR(parser::OmpInteropPreference);
DECLARE_DESCRIPTOR(parser::OmpInteropType);
DECLARE_DESCRIPTOR(parser::OmpIterator);
DECLARE_DESCRIPTOR(parser::OmpLastprivateModifier);
DECLARE_DESCRIPTOR(parser::OmpLinearModifier);

View File

@ -424,6 +424,9 @@ extractOmpDirective(const parser::OpenMPConstruct &ompConstruct) {
},
[](const parser::OpenMPDepobjConstruct &c) {
return llvm::omp::OMPD_depobj;
},
[](const parser::OpenMPInteropConstruct &c) {
return llvm::omp::OMPD_interop;
}},
c.u);
},
@ -3363,6 +3366,13 @@ static void genOMP(lower::AbstractConverter &converter, lower::SymMap &symTable,
TODO(converter.getCurrentLocation(), "OpenMPDepobjConstruct");
}
static void genOMP(lower::AbstractConverter &converter, lower::SymMap &symTable,
semantics::SemanticsContext &semaCtx,
lower::pft::Evaluation &eval,
const parser::OpenMPInteropConstruct &interopConstruct) {
TODO(converter.getCurrentLocation(), "OpenMPInteropConstruct");
}
static void
genOMP(lower::AbstractConverter &converter, lower::SymMap &symTable,
semantics::SemanticsContext &semaCtx, lower::pft::Evaluation &eval,

View File

@ -425,6 +425,17 @@ TYPE_PARSER(construct<OmpDeviceModifier>(
TYPE_PARSER(construct<OmpExpectation>( //
"PRESENT" >> pure(OmpExpectation::Value::Present)))
TYPE_PARSER(construct<OmpInteropRuntimeIdentifier>(
construct<OmpInteropRuntimeIdentifier>(charLiteralConstant) ||
construct<OmpInteropRuntimeIdentifier>(scalarIntConstantExpr)))
TYPE_PARSER(construct<OmpInteropPreference>(verbatim("PREFER_TYPE"_tok) >>
parenthesized(nonemptyList(Parser<OmpInteropRuntimeIdentifier>{}))))
TYPE_PARSER(construct<OmpInteropType>(
"TARGETSYNC" >> pure(OmpInteropType::Value::TargetSync) ||
"TARGET" >> pure(OmpInteropType::Value::Target)))
TYPE_PARSER(construct<OmpIteratorSpecifier>(
// Using Parser<TypeDeclarationStmt> or Parser<EntityDecl> has the problem
// that they will attempt to treat what follows the '=' as initialization.
@ -552,6 +563,11 @@ TYPE_PARSER(sourced(
TYPE_PARSER(sourced(construct<OmpIfClause::Modifier>(OmpDirectiveNameParser{})))
TYPE_PARSER(sourced(
construct<OmpInitClause::Modifier>(
construct<OmpInitClause::Modifier>(Parser<OmpInteropPreference>{})) ||
construct<OmpInitClause::Modifier>(Parser<OmpInteropType>{})))
TYPE_PARSER(sourced(construct<OmpInReductionClause::Modifier>(
Parser<OmpReductionIdentifier>{})))
@ -788,6 +804,11 @@ TYPE_PARSER(
// OpenMPv5.2 12.5.2 detach-clause -> DETACH (event-handle)
TYPE_PARSER(construct<OmpDetachClause>(Parser<OmpObject>{}))
// init clause
TYPE_PARSER(construct<OmpInitClause>(
maybe(nonemptyList(Parser<OmpInitClause::Modifier>{}) / ":"),
Parser<OmpObject>{}))
// 2.8.1 ALIGNED (list: alignment)
TYPE_PARSER(construct<OmpAlignedClause>(Parser<OmpObjectList>{},
maybe(":" >> nonemptyList(Parser<OmpAlignedClause::Modifier>{}))))
@ -927,6 +948,8 @@ TYPE_PARSER( //
"IF" >> construct<OmpClause>(construct<OmpClause::If>(
parenthesized(Parser<OmpIfClause>{}))) ||
"INBRANCH" >> construct<OmpClause>(construct<OmpClause::Inbranch>()) ||
"INIT" >> construct<OmpClause>(construct<OmpClause::Init>(
parenthesized(Parser<OmpInitClause>{}))) ||
"INCLUSIVE" >> construct<OmpClause>(construct<OmpClause::Inclusive>(
parenthesized(Parser<OmpObjectList>{}))) ||
"INITIALIZER" >> construct<OmpClause>(construct<OmpClause::Initializer>(
@ -1016,6 +1039,8 @@ TYPE_PARSER( //
parenthesized(scalarIntExpr))) ||
"TO" >> construct<OmpClause>(construct<OmpClause::To>(
parenthesized(Parser<OmpToClause>{}))) ||
"USE" >> construct<OmpClause>(construct<OmpClause::Use>(
parenthesized(Parser<OmpObject>{}))) ||
"USE_DEVICE_PTR" >> construct<OmpClause>(construct<OmpClause::UseDevicePtr>(
parenthesized(Parser<OmpObjectList>{}))) ||
"USE_DEVICE_ADDR" >>
@ -1251,6 +1276,13 @@ TYPE_PARSER(sourced( //
IsDirective(llvm::omp::Directive::OMPD_depobj)) >=
Parser<OmpDirectiveSpecification>{})))
// OMP 5.2 14.1 Interop construct
TYPE_PARSER(sourced( //
construct<OpenMPInteropConstruct>(
predicated(OmpDirectiveNameParser{},
IsDirective(llvm::omp::Directive::OMPD_interop)) >=
Parser<OmpDirectiveSpecification>{})))
// Standalone Constructs
TYPE_PARSER(
sourced( //
@ -1263,7 +1295,9 @@ TYPE_PARSER(
construct<OpenMPStandaloneConstruct>(Parser<OpenMPCancelConstruct>{}) ||
construct<OpenMPStandaloneConstruct>(
Parser<OmpMetadirectiveDirective>{}) ||
construct<OpenMPStandaloneConstruct>(Parser<OpenMPDepobjConstruct>{})) /
construct<OpenMPStandaloneConstruct>(Parser<OpenMPDepobjConstruct>{}) ||
construct<OpenMPStandaloneConstruct>(
Parser<OpenMPInteropConstruct>{})) /
endOfLine)
// Directives enclosing structured-block

View File

@ -2180,6 +2180,30 @@ public:
Walk(std::get<std::optional<std::list<Modifier>>>(x.t), ": ");
Walk(std::get<OmpObjectList>(x.t));
}
void Unparse(const OmpInteropPreference &x) { Walk(x.v, ","); }
void Unparse(const OmpInitClause &x) {
using Modifier = OmpInitClause::Modifier;
auto &modifiers{std::get<std::optional<std::list<Modifier>>>(x.t)};
bool isTypeStart{true};
for (const Modifier &m : *modifiers) {
if (auto *interopPreferenceMod{
std::get_if<parser::OmpInteropPreference>(&m.u)}) {
Put("PREFER_TYPE(");
Walk(*interopPreferenceMod);
Put("),");
} else if (auto *interopTypeMod{
std::get_if<parser::OmpInteropType>(&m.u)}) {
if (isTypeStart) {
isTypeStart = false;
} else {
Put(",");
}
Walk(*interopTypeMod);
}
}
Put(": ");
Walk(std::get<OmpObject>(x.t));
}
void Unparse(const OmpMapClause &x) {
using Modifier = OmpMapClause::Modifier;
Walk(std::get<std::optional<std::list<Modifier>>>(x.t), ": ");
@ -2710,6 +2734,22 @@ public:
Put("\n");
EndOpenMP();
}
void Unparse(const OpenMPInteropConstruct &x) {
BeginOpenMP();
Word("!$OMP INTEROP");
using Flags = OmpDirectiveSpecification::Flags;
if (std::get<Flags>(x.v.t) == Flags::DeprecatedSyntax) {
Walk("(", std::get<std::optional<OmpArgumentList>>(x.v.t), ")");
Walk(" ", std::get<std::optional<OmpClauseList>>(x.v.t));
} else {
Walk(" ", std::get<std::optional<OmpClauseList>>(x.v.t));
Walk(" (", std::get<std::optional<OmpArgumentList>>(x.v.t), ")");
}
Put("\n");
EndOpenMP();
}
void Unparse(const OpenMPDeclarativeAssumes &x) {
BeginOpenMP();
Word("!$OMP ASSUMES ");
@ -3004,6 +3044,7 @@ public:
OmpDeviceTypeClause, DeviceTypeDescription) // OMP device_type
WALK_NESTED_ENUM(OmpReductionModifier, Value) // OMP reduction-modifier
WALK_NESTED_ENUM(OmpExpectation, Value) // OMP motion-expectation
WALK_NESTED_ENUM(OmpInteropType, Value) // OMP InteropType
WALK_NESTED_ENUM(OmpOrderClause, Ordering) // OMP ordering
WALK_NESTED_ENUM(OmpOrderModifier, Value) // OMP order-modifier
WALK_NESTED_ENUM(OmpPrescriptiveness, Value) // OMP prescriptiveness

View File

@ -5730,6 +5730,88 @@ void OmpStructureChecker::Leave(const parser::DoConstruct &x) {
Base::Leave(x);
}
void OmpStructureChecker::Enter(const parser::OpenMPInteropConstruct &x) {
bool isDependClauseOccured{false};
int targetCount{0}, targetSyncCount{0};
const auto &dir{std::get<parser::OmpDirectiveName>(x.v.t)};
std::set<const Symbol *> objectSymbolList;
PushContextAndClauseSets(dir.source, llvm::omp::Directive::OMPD_interop);
const auto &clauseList{std::get<std::optional<parser::OmpClauseList>>(x.v.t)};
for (const auto &clause : clauseList->v) {
common::visit(
common::visitors{
[&](const parser::OmpClause::Init &initClause) {
if (OmpVerifyModifiers(initClause.v, llvm::omp::OMPC_init,
GetContext().directiveSource, context_)) {
auto &modifiers{OmpGetModifiers(initClause.v)};
auto &&interopTypeModifier{
OmpGetRepeatableModifier<parser::OmpInteropType>(
modifiers)};
for (const auto &it : interopTypeModifier) {
if (it->v == parser::OmpInteropType::Value::TargetSync) {
++targetSyncCount;
} else {
++targetCount;
}
}
}
const auto &interopVar{parser::Unwrap<parser::OmpObject>(
std::get<parser::OmpObject>(initClause.v.t))};
const auto *name{parser::Unwrap<parser::Name>(interopVar)};
const auto *objectSymbol{name->symbol};
if (llvm::is_contained(objectSymbolList, objectSymbol)) {
context_.Say(GetContext().directiveSource,
"Each interop-var may be specified for at most one action-clause of each INTEROP construct."_err_en_US);
} else {
objectSymbolList.insert(objectSymbol);
}
},
[&](const parser::OmpClause::Depend &dependClause) {
isDependClauseOccured = true;
},
[&](const parser::OmpClause::Destroy &destroyClause) {
const auto &interopVar{
parser::Unwrap<parser::OmpObject>(destroyClause.v)};
const auto *name{parser::Unwrap<parser::Name>(interopVar)};
const auto *objectSymbol{name->symbol};
if (llvm::is_contained(objectSymbolList, objectSymbol)) {
context_.Say(GetContext().directiveSource,
"Each interop-var may be specified for at most one action-clause of each INTEROP construct."_err_en_US);
} else {
objectSymbolList.insert(objectSymbol);
}
},
[&](const parser::OmpClause::Use &useClause) {
const auto &interopVar{
parser::Unwrap<parser::OmpObject>(useClause.v)};
const auto *name{parser::Unwrap<parser::Name>(interopVar)};
const auto *objectSymbol{name->symbol};
if (llvm::is_contained(objectSymbolList, objectSymbol)) {
context_.Say(GetContext().directiveSource,
"Each interop-var may be specified for at most one action-clause of each INTEROP construct."_err_en_US);
} else {
objectSymbolList.insert(objectSymbol);
}
},
[&](const auto &) {},
},
clause.u);
}
if (targetCount > 1 || targetSyncCount > 1) {
context_.Say(GetContext().directiveSource,
"Each interop-type may be specified at most once."_err_en_US);
}
if (isDependClauseOccured && !targetSyncCount) {
context_.Say(GetContext().directiveSource,
"A DEPEND clause can only appear on the directive if the interop-type includes TARGETSYNC"_err_en_US);
}
}
void OmpStructureChecker::Leave(const parser::OpenMPInteropConstruct &) {
dirContext_.pop_back();
}
void OmpStructureChecker::CheckAllowedRequiresClause(llvmOmpClause clause) {
CheckAllowedClause(clause);

View File

@ -73,6 +73,8 @@ public:
void Enter(const parser::OpenMPConstruct &);
void Leave(const parser::OpenMPConstruct &);
void Enter(const parser::OpenMPInteropConstruct &);
void Leave(const parser::OpenMPInteropConstruct &);
void Enter(const parser::OpenMPDeclarativeConstruct &);
void Leave(const parser::OpenMPDeclarativeConstruct &);

View File

@ -240,6 +240,38 @@ const OmpModifierDescriptor &OmpGetDescriptor<parser::OmpExpectation>() {
return desc;
}
template <>
const OmpModifierDescriptor &OmpGetDescriptor<parser::OmpInteropPreference>() {
static const OmpModifierDescriptor desc{
/*name=*/"interop-preference",
/*props=*/
{
{52, {OmpProperty::Unique}},
},
/*clauses=*/
{
{52, {Clause::OMPC_init}},
},
};
return desc;
}
template <>
const OmpModifierDescriptor &OmpGetDescriptor<parser::OmpInteropType>() {
static const OmpModifierDescriptor desc{
/*name=*/"interop-type",
/*props=*/
{
{52, {OmpProperty::Required}},
},
/*clauses=*/
{
{52, {Clause::OMPC_init}},
},
};
return desc;
}
template <>
const OmpModifierDescriptor &OmpGetDescriptor<parser::OmpIterator>() {
static const OmpModifierDescriptor desc{

View File

@ -0,0 +1,9 @@
! REQUIRES: openmp_runtime
! RUN: %not_todo_cmd %flang_fc1 -emit-llvm %openmp_flags -fopenmp-version=52 -o - %s 2>&1 | FileCheck %s
! CHECK: not yet implemented: OpenMPInteropConstruct
program interop_test
use omp_lib
integer(omp_interop_kind) :: obj
!$omp interop init(targetsync,target: obj)
end program interop_test

View File

@ -0,0 +1,209 @@
! REQUIRES: openmp_runtime
! RUN: %flang_fc1 -fdebug-unparse -fopenmp-version=52 %openmp_flags %s | FileCheck --ignore-case --check-prefix="UNPARSE" %s
! RUN: %flang_fc1 -fdebug-dump-parse-tree-no-sema -fopenmp-version=52 %openmp_flags %s | FileCheck --check-prefix="PARSE-TREE" %s
SUBROUTINE test_interop_01()
!$OMP INTEROP DEVICE(1)
PRINT *,'pass'
END SUBROUTINE test_interop_01
!UNPARSE: SUBROUTINE test_interop_01
!UNPARSE: !$OMP INTEROP DEVICE(1_4)
!UNPARSE: PRINT *, "pass"
!UNPARSE: END SUBROUTINE test_interop_01
!PARSE-TREE: | SubroutineStmt
!PARSE-TREE: | | Name = 'test_interop_01'
!PARSE-TREE: | SpecificationPart
!PARSE-TREE: | | ImplicitPart ->
!PARSE-TREE: | ExecutionPart -> Block
!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPInteropConstruct -> OmpDirectiveSpecification
!PARSE-TREE: | | | OmpDirectiveName -> llvm::omp::Directive = interop
!PARSE-TREE: | | | OmpClauseList -> OmpClause -> Device -> OmpDeviceClause
!PARSE-TREE: | | | | Scalar -> Integer -> Expr -> LiteralConstant -> IntLiteralConstant = '1'
!PARSE-TREE: | | | Flags = None
!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> PrintStmt
!PARSE-TREE: | | | Format -> Star
!PARSE-TREE: | | | OutputItem -> Expr -> LiteralConstant -> CharLiteralConstant
!PARSE-TREE: | | | | string = 'pass'
!PARSE-TREE: | EndSubroutineStmt -> Name = 'test_interop_01'
SUBROUTINE test_interop_02()
USE omp_lib
INTEGER(OMP_INTEROP_KIND) :: obj1, obj2, obj3
!$OMP INTEROP INIT(TARGETSYNC: obj) USE(obj1) DESTROY(obj3)
PRINT *,'pass'
END SUBROUTINE test_interop_02
!UNPARSE: SUBROUTINE test_interop_02
!UNPARSE: USE :: omp_lib
!UNPARSE: INTEGER(KIND=8_4) obj1, obj2, obj3
!UNPARSE: !$OMP INTEROP INIT(TARGETSYNC: obj) USE(obj1) DESTROY(obj3)
!UNPARSE: PRINT *, "pass"
!UNPARSE: END SUBROUTINE test_interop_02
!PARSE-TREE: | SubroutineStmt
!PARSE-TREE: | | Name = 'test_interop_02'
!PARSE-TREE: | SpecificationPart
!PARSE-TREE: | | UseStmt
!PARSE-TREE: | | | Name = 'omp_lib'
!PARSE-TREE: | | ImplicitPart ->
!PARSE-TREE: | | DeclarationConstruct -> SpecificationConstruct -> TypeDeclarationStmt
!PARSE-TREE: | | | DeclarationTypeSpec -> IntrinsicTypeSpec -> IntegerTypeSpec -> KindSelector -> Scalar -> Integer -> Constant -> Expr -> Designator -> DataRef -> Name = 'omp_interop_kind'
!PARSE-TREE: | | | EntityDecl
!PARSE-TREE: | | | | Name = 'obj1'
!PARSE-TREE: | | | EntityDecl
!PARSE-TREE: | | | | Name = 'obj2'
!PARSE-TREE: | | | EntityDecl
!PARSE-TREE: | | | | Name = 'obj3'
!PARSE-TREE: | ExecutionPart -> Block
!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPInteropConstruct -> OmpDirectiveSpecification
!PARSE-TREE: | | | OmpDirectiveName -> llvm::omp::Directive = interop
!PARSE-TREE: | | | OmpClauseList -> OmpClause -> Init -> OmpInitClause
!PARSE-TREE: | | | | Modifier -> OmpInteropType -> Value = TargetSync
!PARSE-TREE: | | | | OmpObject -> Designator -> DataRef -> Name = 'obj'
!PARSE-TREE: | | | OmpClause -> Use -> OmpUseClause -> OmpObject -> Designator -> DataRef -> Name = 'obj1'
!PARSE-TREE: | | | OmpClause -> Destroy -> OmpDestroyClause -> OmpObject -> Designator -> DataRef -> Name = 'obj3'
!PARSE-TREE: | | | Flags = None
!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> PrintStmt
!PARSE-TREE: | | | Format -> Star
!PARSE-TREE: | | | OutputItem -> Expr -> LiteralConstant -> CharLiteralConstant
!PARSE-TREE: | | | | string = 'pass'
!PARSE-TREE: | EndSubroutineStmt -> Name = 'test_interop_02'
SUBROUTINE test_interop_03()
USE omp_lib
INTEGER(OMP_INTEROP_KIND) :: obj
!$OMP INTEROP INIT(TARGETSYNC: obj) DEPEND(INOUT: obj)
PRINT *,'pass'
END SUBROUTINE test_interop_03
!UNPARSE: SUBROUTINE test_interop_03
!UNPARSE: USE :: omp_lib
!UNPARSE: INTEGER(KIND=8_4) obj
!UNPARSE: !$OMP INTEROP INIT(TARGETSYNC: obj) DEPEND(INOUT: obj)
!UNPARSE: PRINT *, "pass"
!UNPARSE: END SUBROUTINE test_interop_03
!PARSE-TREE: | SubroutineStmt
!PARSE-TREE: | | Name = 'test_interop_03'
!PARSE-TREE: | SpecificationPart
!PARSE-TREE: | | UseStmt
!PARSE-TREE: | | | Name = 'omp_lib'
!PARSE-TREE: | | ImplicitPart ->
!PARSE-TREE: | | DeclarationConstruct -> SpecificationConstruct -> TypeDeclarationStmt
!PARSE-TREE: | | | DeclarationTypeSpec -> IntrinsicTypeSpec -> IntegerTypeSpec -> KindSelector -> Scalar -> Integer -> Constant -> Expr -> Designator -> DataRef -> Name = 'omp_interop_kind'
!PARSE-TREE: | | | EntityDecl
!PARSE-TREE: | | | | Name = 'obj'
!PARSE-TREE: | ExecutionPart -> Block
!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPInteropConstruct -> OmpDirectiveSpecification
!PARSE-TREE: | | | OmpDirectiveName -> llvm::omp::Directive = interop
!PARSE-TREE: | | | OmpClauseList -> OmpClause -> Init -> OmpInitClause
!PARSE-TREE: | | | | Modifier -> OmpInteropType -> Value = TargetSync
!PARSE-TREE: | | | | OmpObject -> Designator -> DataRef -> Name = 'obj'
!PARSE-TREE: | | | OmpClause -> Depend -> OmpDependClause -> TaskDep
!PARSE-TREE: | | | | Modifier -> OmpTaskDependenceType -> Value = Inout
!PARSE-TREE: | | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'obj'
!PARSE-TREE: | | | Flags = None
!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> PrintStmt
!PARSE-TREE: | | | Format -> Star
!PARSE-TREE: | | | OutputItem -> Expr -> LiteralConstant -> CharLiteralConstant
!PARSE-TREE: | | | | string = 'pass'
!PARSE-TREE: | EndSubroutineStmt -> Name = 'test_interop_03'
SUBROUTINE test_interop_04()
USE omp_lib
INTEGER(OMP_INTEROP_KIND) :: obj
INTEGER, DIMENSION(1,10) :: arr
!$OMP INTEROP INIT(PREFER_TYPE("cuda"),TARGETSYNC,TARGET: obj) DEPEND(INOUT: arr) NOWAIT
PRINT *,'pass'
END SUBROUTINE test_interop_04
!UNPARSE: SUBROUTINE test_interop_04
!UNPARSE: USE :: omp_lib
!UNPARSE: INTEGER(KIND=8_4) obj
!UNPARSE: INTEGER, DIMENSION(1_4,10_4) :: arr
!UNPARSE: !$OMP INTEROP INIT(PREFER_TYPE("cuda"),TARGETSYNC,TARGET: obj) DEPEND(INOUT: &
!UNPARSE: !$OMP&arr) NOWAIT
!UNPARSE: PRINT *, "pass"
!UNPARSE: END SUBROUTINE test_interop_04
!PARSE-TREE: | SubroutineStmt
!PARSE-TREE: | | Name = 'test_interop_04'
!PARSE-TREE: | SpecificationPart
!PARSE-TREE: | | UseStmt
!PARSE-TREE: | | | Name = 'omp_lib'
!PARSE-TREE: | | ImplicitPart ->
!PARSE-TREE: | | DeclarationConstruct -> SpecificationConstruct -> TypeDeclarationStmt
!PARSE-TREE: | | | DeclarationTypeSpec -> IntrinsicTypeSpec -> IntegerTypeSpec -> KindSelector -> Scalar -> Integer -> Constant -> Expr -> Designator -> DataRef -> Name = 'omp_interop_kind'
!PARSE-TREE: | | | EntityDecl
!PARSE-TREE: | | | | Name = 'obj'
!PARSE-TREE: | | DeclarationConstruct -> SpecificationConstruct -> TypeDeclarationStmt
!PARSE-TREE: | | | DeclarationTypeSpec -> IntrinsicTypeSpec -> IntegerTypeSpec ->
!PARSE-TREE: | | | AttrSpec -> ArraySpec -> ExplicitShapeSpec
!PARSE-TREE: | | | | SpecificationExpr -> Scalar -> Integer -> Expr -> LiteralConstant -> IntLiteralConstant = '1'
!PARSE-TREE: | | | ExplicitShapeSpec
!PARSE-TREE: | | | | SpecificationExpr -> Scalar -> Integer -> Expr -> LiteralConstant -> IntLiteralConstant = '10'
!PARSE-TREE: | | | EntityDecl
!PARSE-TREE: | | | | Name = 'arr'
!PARSE-TREE: | ExecutionPart -> Block
!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPInteropConstruct -> OmpDirectiveSpecification
!PARSE-TREE: | | | OmpDirectiveName -> llvm::omp::Directive = interop
!PARSE-TREE: | | | OmpClauseList -> OmpClause -> Init -> OmpInitClause
!PARSE-TREE: | | | | Modifier -> OmpInteropPreference -> OmpInteropRuntimeIdentifier -> CharLiteralConstant
!PARSE-TREE: | | | | | string = 'cuda'
!PARSE-TREE: | | | | Modifier -> OmpInteropType -> Value = TargetSync
!PARSE-TREE: | | | | Modifier -> OmpInteropType -> Value = Target
!PARSE-TREE: | | | | OmpObject -> Designator -> DataRef -> Name = 'obj'
!PARSE-TREE: | | | OmpClause -> Depend -> OmpDependClause -> TaskDep
!PARSE-TREE: | | | | Modifier -> OmpTaskDependenceType -> Value = Inout
!PARSE-TREE: | | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'arr'
!PARSE-TREE: | | | OmpClause -> Nowait
!PARSE-TREE: | | | Flags = None
!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> PrintStmt
!PARSE-TREE: | | | Format -> Star
!PARSE-TREE: | | | OutputItem -> Expr -> LiteralConstant -> CharLiteralConstant
!PARSE-TREE: | | | | string = 'pass'
!PARSE-TREE: | EndSubroutineStmt -> Name = 'test_interop_04'
SUBROUTINE test_interop_05()
USE omp_lib
INTEGER(OMP_INTEROP_KIND) :: obj
!$OMP INTEROP INIT(PREFER_TYPE(omp_ifr_sycl), TARGETSYNC: obj) DEVICE(DEVICE_NUM:0)
PRINT *,'pass'
END SUBROUTINE test_interop_05
!UNPARSE: SUBROUTINE test_interop_05
!UNPARSE: USE :: omp_lib
!UNPARSE: INTEGER(KIND=8_4) obj
!UNPARSE: !$OMP INTEROP INIT(PREFER_TYPE(4_4),TARGETSYNC: obj) DEVICE(DEVICE_NUM: 0_4)
!UNPARSE: PRINT *, "pass"
!UNPARSE: END SUBROUTINE test_interop_05
!PARSE-TREE: | SubroutineStmt
!PARSE-TREE: | | Name = 'test_interop_05'
!PARSE-TREE: | SpecificationPart
!PARSE-TREE: | | UseStmt
!PARSE-TREE: | | | Name = 'omp_lib'
!PARSE-TREE: | | ImplicitPart ->
!PARSE-TREE: | | DeclarationConstruct -> SpecificationConstruct -> TypeDeclarationStmt
!PARSE-TREE: | | | DeclarationTypeSpec -> IntrinsicTypeSpec -> IntegerTypeSpec -> KindSelector -> Scalar -> Integer -> Constant -> Expr -> Designator -> DataRef -> Name = 'omp_interop_kind'
!PARSE-TREE: | | | EntityDecl
!PARSE-TREE: | | | | Name = 'obj'
!PARSE-TREE: | ExecutionPart -> Block
!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPInteropConstruct -> OmpDirectiveSpecification
!PARSE-TREE: | | | OmpDirectiveName -> llvm::omp::Directive = interop
!PARSE-TREE: | | | OmpClauseList -> OmpClause -> Init -> OmpInitClause
!PARSE-TREE: | | | | Modifier -> OmpInteropPreference -> OmpInteropRuntimeIdentifier -> Scalar -> Integer -> Constant -> Expr -> Designator -> DataRef -> Name = 'omp_ifr_sycl'
!PARSE-TREE: | | | | Modifier -> OmpInteropType -> Value = TargetSync
!PARSE-TREE: | | | | OmpObject -> Designator -> DataRef -> Name = 'obj'
!PARSE-TREE: | | | OmpClause -> Device -> OmpDeviceClause
!PARSE-TREE: | | | | Modifier -> OmpDeviceModifier -> Value = Device_Num
!PARSE-TREE: | | | | Scalar -> Integer -> Expr -> LiteralConstant -> IntLiteralConstant = '0'
!PARSE-TREE: | | | Flags = None
!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> PrintStmt
!PARSE-TREE: | | | Format -> Star
!PARSE-TREE: | | | OutputItem -> Expr -> LiteralConstant -> CharLiteralConstant
!PARSE-TREE: | | | | string = 'pass'
!PARSE-TREE: | EndSubroutineStmt -> Name = 'test_interop_05'

View File

@ -0,0 +1,30 @@
! REQUIRES: openmp_runtime
! RUN: %python %S/../test_errors.py %s %flang %openmp_flags -fopenmp-version=52
! OpenMP Version 5.2
! 14.1 Interop construct
! To check various semantic errors for inteorp construct.
SUBROUTINE test_interop_01()
USE omp_lib
INTEGER(OMP_INTEROP_KIND) :: obj
!ERROR: Each interop-var may be specified for at most one action-clause of each INTEROP construct.
!$OMP INTEROP INIT(TARGETSYNC,TARGET: obj) USE(obj)
PRINT *, 'pass'
END SUBROUTINE test_interop_01
SUBROUTINE test_interop_02()
USE omp_lib
INTEGER(OMP_INTEROP_KIND) :: obj
!ERROR: Each interop-type may be specified at most once.
!$OMP INTEROP INIT(TARGETSYNC,TARGET,TARGETSYNC: obj)
PRINT *, 'pass'
END SUBROUTINE test_interop_02
SUBROUTINE test_interop_03()
USE omp_lib
INTEGER(OMP_INTEROP_KIND) :: obj
!ERROR: A DEPEND clause can only appear on the directive if the interop-type includes TARGETSYNC
!$OMP INTEROP INIT(TARGET: obj) DEPEND(INOUT: obj)
PRINT *, 'pass'
END SUBROUTINE test_interop_03

View File

@ -244,6 +244,7 @@ def OMPC_Indirect : Clause<"indirect"> {
}
def OMPC_Init : Clause<"init"> {
let clangClass = "OMPInitClause";
let flangClass = "OmpInitClause";
}
def OMPC_Initializer : Clause<"initializer"> {
let flangClass = "OmpInitializerClause";
@ -526,6 +527,7 @@ def OMPC_Update : Clause<"update"> {
}
def OMPC_Use : Clause<"use"> {
let clangClass = "OMPUseClause";
let flangClass = "OmpUseClause";
}
def OMPC_UsesAllocators : Clause<"uses_allocators"> {
let clangClass = "OMPUsesAllocatorsClause";