virtual void DeclarationMarkedOpenMPDeclareTarget(const Decl *D,
const Attr *Attr) {}
+ /// A declaration is marked as a variable with OpenMP allocator.
+ ///
+ /// \param D the declaration marked as a variable with OpenMP allocator.
+ virtual void DeclarationMarkedOpenMPAllocate(const Decl *D, const Attr *A) {}
+
/// A definition has been made visible by being redefined locally.
///
/// \param D The definition that was previously not visible.
Visit(D->getInit());
}
+ void VisitOMPAllocateDecl(const OMPAllocateDecl *D) {
+ for (const auto *E : D->varlists())
+ Visit(E);
+ }
+
template <typename SpecializationDecl>
void dumpTemplateDeclSpecialization(const SpecializationDecl *D) {
for (const auto *RedeclWithBadType : D->redecls()) {
static bool classof(const Decl *D) { return classofKind(D->getKind()); }
static bool classofKind(Kind K) { return K == OMPRequires; }
};
+
+/// This represents '#pragma omp allocate ...' directive.
+/// For example, in the following, the default allocator is used for both 'a'
+/// and 'A::b':
+///
+/// \code
+/// int a;
+/// #pragma omp allocate(a)
+/// struct A {
+/// static int b;
+/// #pragma omp allocate(b)
+/// };
+/// \endcode
+///
+class OMPAllocateDecl final
+ : public Decl,
+ private llvm::TrailingObjects<OMPAllocateDecl, Expr *> {
+ friend class ASTDeclReader;
+ friend TrailingObjects;
+
+ /// Number of variable within the allocate directive.
+ unsigned NumVars = 0;
+
+ virtual void anchor();
+
+ OMPAllocateDecl(Kind DK, DeclContext *DC, SourceLocation L)
+ : Decl(DK, DC, L) {}
+
+ ArrayRef<const Expr *> getVars() const {
+ return llvm::makeArrayRef(getTrailingObjects<Expr *>(), NumVars);
+ }
+
+ MutableArrayRef<Expr *> getVars() {
+ return MutableArrayRef<Expr *>(getTrailingObjects<Expr *>(), NumVars);
+ }
+
+ void setVars(ArrayRef<Expr *> VL);
+
+public:
+ static OMPAllocateDecl *Create(ASTContext &C, DeclContext *DC,
+ SourceLocation L, ArrayRef<Expr *> VL);
+ static OMPAllocateDecl *CreateDeserialized(ASTContext &C, unsigned ID,
+ unsigned N);
+
+ typedef MutableArrayRef<Expr *>::iterator varlist_iterator;
+ typedef ArrayRef<const Expr *>::iterator varlist_const_iterator;
+ typedef llvm::iterator_range<varlist_iterator> varlist_range;
+ typedef llvm::iterator_range<varlist_const_iterator> varlist_const_range;
+
+ unsigned varlist_size() const { return NumVars; }
+ bool varlist_empty() const { return NumVars == 0; }
+
+ varlist_range varlists() {
+ return varlist_range(varlist_begin(), varlist_end());
+ }
+ varlist_const_range varlists() const {
+ return varlist_const_range(varlist_begin(), varlist_end());
+ }
+ varlist_iterator varlist_begin() { return getVars().begin(); }
+ varlist_iterator varlist_end() { return getVars().end(); }
+ varlist_const_iterator varlist_begin() const { return getVars().begin(); }
+ varlist_const_iterator varlist_end() const { return getVars().end(); }
+
+ static bool classof(const Decl *D) { return classofKind(D->getKind()); }
+ static bool classofKind(Kind K) { return K == OMPAllocate; }
+};
+
} // end namespace clang
#endif
DEF_TRAVERSE_DECL(OMPCapturedExprDecl, { TRY_TO(TraverseVarHelper(D)); })
+DEF_TRAVERSE_DECL(OMPAllocateDecl, {
+ for (auto *I : D->varlists()) {
+ TRY_TO(TraverseStmt(I));
+ }
+})
+
// A helper method for TemplateDecl's children.
template <typename Derived>
bool RecursiveASTVisitor<Derived>::TraverseTemplateParameterListHelper(
break;
#include "clang/Basic/OpenMPKinds.def"
case OMPC_threadprivate:
+ case OMPC_allocate:
case OMPC_uniform:
case OMPC_unknown:
break;
}];
}
+def OMPAllocateDecl : InheritableAttr {
+ // This attribute has no spellings as it is only ever created implicitly.
+ let Spellings = [];
+ let SemaHandler = 0;
+ let Documentation = [Undocumented];
+}
+
def InternalLinkage : InheritableAttr {
let Spellings = [Clang<"internal_linkage">];
let Subjects = SubjectList<[Var, Function, CXXRecord]>;
def ClassScopeFunctionSpecialization : Decl;
def Import : Decl;
def OMPThreadPrivate : Decl;
+def OMPAllocate : Decl;
def OMPRequires : Decl;
def Empty : Decl;
OPENMP_DIRECTIVE_EXT(target_teams_distribute_parallel_for, "target teams distribute parallel for")
OPENMP_DIRECTIVE_EXT(target_teams_distribute_parallel_for_simd, "target teams distribute parallel for simd")
OPENMP_DIRECTIVE_EXT(target_teams_distribute_simd, "target teams distribute simd")
+OPENMP_DIRECTIVE(allocate)
// OpenMP clauses.
OPENMP_CLAUSE(if, OMPIfClause)
#include "clang/Basic/OpenMPKinds.def"
OMPC_threadprivate,
OMPC_uniform,
+ OMPC_allocate,
OMPC_unknown
};
// OpenMP directives and clauses.
/// Called on correct id-expression from the '#pragma omp
/// threadprivate'.
- ExprResult ActOnOpenMPIdExpression(Scope *CurScope,
- CXXScopeSpec &ScopeSpec,
- const DeclarationNameInfo &Id);
+ ExprResult ActOnOpenMPIdExpression(Scope *CurScope, CXXScopeSpec &ScopeSpec,
+ const DeclarationNameInfo &Id,
+ OpenMPDirectiveKind Kind);
/// Called on well-formed '#pragma omp threadprivate'.
DeclGroupPtrTy ActOnOpenMPThreadprivateDirective(
SourceLocation Loc,
/// Builds a new OpenMPThreadPrivateDecl and checks its correctness.
OMPThreadPrivateDecl *CheckOMPThreadPrivateDecl(SourceLocation Loc,
ArrayRef<Expr *> VarList);
+ /// Called on well-formed '#pragma omp allocate'.
+ DeclGroupPtrTy ActOnOpenMPAllocateDirective(SourceLocation Loc,
+ ArrayRef<Expr *> VarList,
+ DeclContext *Owner = nullptr);
/// Called on well-formed '#pragma omp requires'.
DeclGroupPtrTy ActOnOpenMPRequiresDirective(SourceLocation Loc,
ArrayRef<OMPClause *> ClauseList);
/// An OMPRequiresDecl record.
DECL_OMP_REQUIRES,
-
+
+ /// An OMPAllocateDcl record.
+ DECL_OMP_ALLOCATE,
+
/// An EmptyDecl record.
DECL_EMPTY,
void DeclarationMarkedOpenMPThreadPrivate(const Decl *D) override;
void DeclarationMarkedOpenMPDeclareTarget(const Decl *D,
const Attr *Attr) override;
+ void DeclarationMarkedOpenMPAllocate(const Decl *D, const Attr *A) override;
void RedefinedHiddenDefinition(const NamedDecl *D, Module *M) override;
void AddedAttributeToRecord(const Attr *Attr,
const RecordDecl *Record) override;
return false;
} else if (isa<PragmaCommentDecl>(D))
return true;
- else if (isa<OMPThreadPrivateDecl>(D))
- return true;
else if (isa<PragmaDetectMismatchDecl>(D))
return true;
else if (isa<OMPThreadPrivateDecl>(D))
return !D->getDeclContext()->isDependentContext();
+ else if (isa<OMPAllocateDecl>(D))
+ return !D->getDeclContext()->isDependentContext();
else if (isa<OMPDeclareReductionDecl>(D))
return !D->getDeclContext()->isDependentContext();
else if (isa<ImportDecl>(D))
case ObjCCategoryImpl:
case Import:
case OMPThreadPrivate:
+ case OMPAllocate:
case OMPRequires:
case OMPCapturedExpr:
case Empty:
std::uninitialized_copy(VL.begin(), VL.end(), getTrailingObjects<Expr *>());
}
+//===----------------------------------------------------------------------===//
+// OMPAllocateDecl Implementation.
+//===----------------------------------------------------------------------===//
+
+void OMPAllocateDecl::anchor() { }
+
+OMPAllocateDecl *OMPAllocateDecl::Create(ASTContext &C, DeclContext *DC,
+ SourceLocation L,
+ ArrayRef<Expr *> VL) {
+ OMPAllocateDecl *D = new (C, DC, additionalSizeToAlloc<Expr *>(VL.size()))
+ OMPAllocateDecl(OMPAllocate, DC, L);
+ D->NumVars = VL.size();
+ D->setVars(VL);
+ return D;
+}
+
+OMPAllocateDecl *OMPAllocateDecl::CreateDeserialized(ASTContext &C, unsigned ID,
+ unsigned N) {
+ OMPAllocateDecl *D = new (C, ID, additionalSizeToAlloc<Expr *>(N))
+ OMPAllocateDecl(OMPAllocate, nullptr, SourceLocation());
+ D->NumVars = N;
+ return D;
+}
+
+void OMPAllocateDecl::setVars(ArrayRef<Expr *> VL) {
+ assert(VL.size() == NumVars &&
+ "Number of variables is not the same as the preallocated buffer");
+ std::uninitialized_copy(VL.begin(), VL.end(), getTrailingObjects<Expr *>());
+}
+
//===----------------------------------------------------------------------===//
// OMPRequiresDecl Implementation.
//===----------------------------------------------------------------------===//
void VisitUsingDecl(UsingDecl *D);
void VisitUsingShadowDecl(UsingShadowDecl *D);
void VisitOMPThreadPrivateDecl(OMPThreadPrivateDecl *D);
+ void VisitOMPAllocateDecl(OMPAllocateDecl *D);
void VisitOMPRequiresDecl(OMPRequiresDecl *D);
void VisitOMPDeclareReductionDecl(OMPDeclareReductionDecl *D);
void VisitOMPDeclareMapperDecl(OMPDeclareMapperDecl *D);
// FIXME: Need to be able to tell the DeclPrinter when
const char *Terminator = nullptr;
if (isa<OMPThreadPrivateDecl>(*D) || isa<OMPDeclareReductionDecl>(*D) ||
- isa<OMPDeclareMapperDecl>(*D) || isa<OMPRequiresDecl>(*D))
+ isa<OMPDeclareMapperDecl>(*D) || isa<OMPRequiresDecl>(*D) ||
+ isa<OMPAllocateDecl>(*D))
Terminator = nullptr;
else if (isa<ObjCMethodDecl>(*D) && cast<ObjCMethodDecl>(*D)->hasBody())
Terminator = nullptr;
}
}
+void DeclPrinter::VisitOMPAllocateDecl(OMPAllocateDecl *D) {
+ Out << "#pragma omp allocate";
+ if (!D->varlist_empty()) {
+ for (OMPAllocateDecl::varlist_iterator I = D->varlist_begin(),
+ E = D->varlist_end();
+ I != E; ++I) {
+ Out << (I == D->varlist_begin() ? '(' : ',');
+ NamedDecl *ND = cast<DeclRefExpr>(*I)->getDecl();
+ ND->printQualifiedName(Out);
+ }
+ Out << ")";
+ }
+}
+
void DeclPrinter::VisitOMPRequiresDecl(OMPRequiresDecl *D) {
Out << "#pragma omp requires ";
if (!D->clauselist_empty()) {
case OMPC_untied:
case OMPC_mergeable:
case OMPC_threadprivate:
+ case OMPC_allocate:
case OMPC_flush:
case OMPC_read:
case OMPC_write:
case OMPC_untied:
case OMPC_mergeable:
case OMPC_threadprivate:
+ case OMPC_allocate:
case OMPC_flush:
case OMPC_read:
case OMPC_write:
return "uniform";
case OMPC_threadprivate:
return "threadprivate or thread local";
+ case OMPC_allocate:
+ return "allocate";
}
llvm_unreachable("Invalid OpenMP clause kind");
}
.Default(OMPC_ATOMIC_DEFAULT_MEM_ORDER_unknown);
case OMPC_unknown:
case OMPC_threadprivate:
+ case OMPC_allocate:
case OMPC_if:
case OMPC_final:
case OMPC_num_threads:
llvm_unreachable("Invalid OpenMP 'atomic_default_mem_order' clause type");
case OMPC_unknown:
case OMPC_threadprivate:
+ case OMPC_allocate:
case OMPC_if:
case OMPC_final:
case OMPC_num_threads:
case OMPD_end_declare_target:
case OMPD_unknown:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_section:
case OMPD_master:
case OMPD_taskyield:
CaptureRegions.push_back(OMPD_unknown);
break;
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_taskyield:
case OMPD_barrier:
case OMPD_taskwait:
case Decl::Label: // __label__ x;
case Decl::Import:
case Decl::OMPThreadPrivate:
+ case Decl::OMPAllocate:
case Decl::OMPCapturedExpr:
case Decl::OMPRequires:
case Decl::Empty:
case OMPD_cancellation_point:
case OMPD_ordered:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_task:
case OMPD_simd:
case OMPD_sections:
case OMPD_cancellation_point:
case OMPD_ordered:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_task:
case OMPD_simd:
case OMPD_sections:
case OMPD_cancellation_point:
case OMPD_ordered:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_task:
case OMPD_simd:
case OMPD_sections:
isa<PragmaDetectMismatchDecl>(D) || isa<UsingDecl>(D) ||
isa<UsingDirectiveDecl>(D) ||
isa<OMPDeclareReductionDecl>(D) ||
- isa<OMPThreadPrivateDecl>(D))
+ isa<OMPThreadPrivateDecl>(D) || isa<OMPAllocateDecl>(D))
return true;
const auto *VD = dyn_cast<VarDecl>(D);
if (!VD)
case OMPD_cancellation_point:
case OMPD_ordered:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_task:
case OMPD_simd:
case OMPD_sections:
case OMPD_cancellation_point:
case OMPD_ordered:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_task:
case OMPD_simd:
case OMPD_sections:
case OMPD_cancellation_point:
case OMPD_ordered:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_task:
case OMPD_simd:
case OMPD_sections:
case OMPD_cancellation_point:
case OMPD_ordered:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_task:
case OMPD_simd:
case OMPD_sections:
case OMPC_nowait:
case OMPC_untied:
case OMPC_threadprivate:
+ case OMPC_allocate:
case OMPC_depend:
case OMPC_mergeable:
case OMPC_device:
EmitOMPThreadPrivateDecl(cast<OMPThreadPrivateDecl>(D));
break;
+ case Decl::OMPAllocate:
+ break;
+
case Decl::OMPDeclareReduction:
EmitOMPDeclareReduction(cast<OMPDeclareReductionDecl>(D));
break;
const ObjCInterfaceDecl *IFD) override;
void DeclarationMarkedUsed(const Decl *D) override;
void DeclarationMarkedOpenMPThreadPrivate(const Decl *D) override;
+ void DeclarationMarkedOpenMPAllocate(const Decl *D, const Attr *A) override;
void DeclarationMarkedOpenMPDeclareTarget(const Decl *D,
const Attr *Attr) override;
void RedefinedHiddenDefinition(const NamedDecl *D, Module *M) override;
for (size_t i = 0, e = Listeners.size(); i != e; ++i)
Listeners[i]->DeclarationMarkedOpenMPThreadPrivate(D);
}
+void MultiplexASTMutationListener::DeclarationMarkedOpenMPAllocate(
+ const Decl *D, const Attr *A) {
+ for (ASTMutationListener *L : Listeners)
+ L->DeclarationMarkedOpenMPAllocate(D, A);
+}
void MultiplexASTMutationListener::DeclarationMarkedOpenMPDeclareTarget(
const Decl *D, const Attr *Attr) {
for (auto *L : Listeners)
/// [C++11] attribute-specifier-seq decl-specifier-seq[opt]
/// init-declarator-list ';'
///[C90/C++]init-declarator-list ';' [TODO]
-/// [OMP] threadprivate-directive [TODO]
+/// [OMP] threadprivate-directive
+/// [OMP] allocate-directive [TODO]
///
/// for-range-declaration: [C++11 6.5p1: stmt.ranged]
/// attribute-specifier-seq[opt] type-specifier-seq declarator
OMPD_mapper,
};
-class ThreadprivateListParserHelper final {
+class DeclDirectiveListParserHelper final {
SmallVector<Expr *, 4> Identifiers;
Parser *P;
+ OpenMPDirectiveKind Kind;
public:
- ThreadprivateListParserHelper(Parser *P) : P(P) {}
+ DeclDirectiveListParserHelper(Parser *P, OpenMPDirectiveKind Kind)
+ : P(P), Kind(Kind) {}
void operator()(CXXScopeSpec &SS, DeclarationNameInfo NameInfo) {
- ExprResult Res =
- P->getActions().ActOnOpenMPIdExpression(P->getCurScope(), SS, NameInfo);
+ ExprResult Res = P->getActions().ActOnOpenMPIdExpression(
+ P->getCurScope(), SS, NameInfo, Kind);
if (Res.isUsable())
Identifiers.push_back(Res.get());
}
/// annot_pragma_openmp 'threadprivate' simple-variable-list
/// annot_pragma_openmp_end
///
+/// allocate-directive:
+/// annot_pragma_openmp 'allocate' simple-variable-list
+/// annot_pragma_openmp_end
+///
/// declare-reduction-directive:
/// annot_pragma_openmp 'declare' 'reduction' [...]
/// annot_pragma_openmp_end
switch (DKind) {
case OMPD_threadprivate: {
ConsumeToken();
- ThreadprivateListParserHelper Helper(this);
- if (!ParseOpenMPSimpleVarList(OMPD_threadprivate, Helper, true)) {
+ DeclDirectiveListParserHelper Helper(this, DKind);
+ if (!ParseOpenMPSimpleVarList(DKind, Helper,
+ /*AllowScopeSpecifier=*/true)) {
// The last seen token is annot_pragma_openmp_end - need to check for
// extra tokens.
if (Tok.isNot(tok::annot_pragma_openmp_end)) {
Diag(Tok, diag::warn_omp_extra_tokens_at_eol)
- << getOpenMPDirectiveName(OMPD_threadprivate);
+ << getOpenMPDirectiveName(DKind);
SkipUntil(tok::annot_pragma_openmp_end, StopBeforeMatch);
}
// Skip the last annot_pragma_openmp_end.
}
break;
}
+ case OMPD_allocate: {
+ ConsumeToken();
+ DeclDirectiveListParserHelper Helper(this, DKind);
+ if (!ParseOpenMPSimpleVarList(DKind, Helper,
+ /*AllowScopeSpecifier=*/true)) {
+ // The last seen token is annot_pragma_openmp_end - need to check for
+ // extra tokens.
+ if (Tok.isNot(tok::annot_pragma_openmp_end)) {
+ Diag(Tok, diag::warn_omp_extra_tokens_at_eol)
+ << getOpenMPDirectiveName(DKind);
+ SkipUntil(tok::annot_pragma_openmp_end, StopBeforeMatch);
+ }
+ // Skip the last annot_pragma_openmp_end.
+ ConsumeAnnotationToken();
+ return Actions.ActOnOpenMPAllocateDirective(Loc, Helper.getIdentifiers());
+ }
+ break;
+ }
case OMPD_requires: {
SourceLocation StartLoc = ConsumeToken();
SmallVector<OMPClause *, 5> Clauses;
/// annot_pragma_openmp 'threadprivate' simple-variable-list
/// annot_pragma_openmp_end
///
+/// allocate-directive:
+/// annot_pragma_openmp 'allocate' simple-variable-list
+/// annot_pragma_openmp_end
+///
/// declare-reduction-directive:
/// annot_pragma_openmp 'declare' 'reduction' '(' <reduction_id> ':'
/// <type> {',' <type>} ':' <expression> ')' ['initializer' '('
<< getOpenMPDirectiveName(DKind) << 0;
}
ConsumeToken();
- ThreadprivateListParserHelper Helper(this);
- if (!ParseOpenMPSimpleVarList(OMPD_threadprivate, Helper, false)) {
+ DeclDirectiveListParserHelper Helper(this, DKind);
+ if (!ParseOpenMPSimpleVarList(DKind, Helper,
+ /*AllowScopeSpecifier=*/false)) {
// The last seen token is annot_pragma_openmp_end - need to check for
// extra tokens.
if (Tok.isNot(tok::annot_pragma_openmp_end)) {
Diag(Tok, diag::warn_omp_extra_tokens_at_eol)
- << getOpenMPDirectiveName(OMPD_threadprivate);
+ << getOpenMPDirectiveName(DKind);
SkipUntil(tok::annot_pragma_openmp_end, StopBeforeMatch);
}
DeclGroupPtrTy Res = Actions.ActOnOpenMPThreadprivateDirective(
SkipUntil(tok::annot_pragma_openmp_end);
break;
}
+ case OMPD_allocate: {
+ // FIXME: Should this be permitted in C++?
+ if ((StmtCtx & ParsedStmtContext::AllowDeclarationsInC) ==
+ ParsedStmtContext()) {
+ Diag(Tok, diag::err_omp_immediate_directive)
+ << getOpenMPDirectiveName(DKind) << 0;
+ }
+ ConsumeToken();
+ DeclDirectiveListParserHelper Helper(this, DKind);
+ if (!ParseOpenMPSimpleVarList(DKind, Helper,
+ /*AllowScopeSpecifier=*/false)) {
+ // The last seen token is annot_pragma_openmp_end - need to check for
+ // extra tokens.
+ if (Tok.isNot(tok::annot_pragma_openmp_end)) {
+ Diag(Tok, diag::warn_omp_extra_tokens_at_eol)
+ << getOpenMPDirectiveName(DKind);
+ SkipUntil(tok::annot_pragma_openmp_end, StopBeforeMatch);
+ }
+ DeclGroupPtrTy Res =
+ Actions.ActOnOpenMPAllocateDirective(Loc, Helper.getIdentifiers());
+ Directive = Actions.ActOnDeclStmt(Res, Loc, Tok.getLocation());
+ }
+ SkipUntil(tok::annot_pragma_openmp_end);
+ break;
+ }
case OMPD_declare_reduction:
ConsumeToken();
if (DeclGroupPtrTy Res =
SkipUntil(tok::annot_pragma_openmp_end, StopBeforeMatch);
break;
case OMPC_threadprivate:
+ case OMPC_allocate:
case OMPC_uniform:
if (!WrongDirective)
Diag(Tok, diag::err_omp_unexpected_clause)
/// declaration: [C99 6.7]
/// declaration-specifiers init-declarator-list[opt] ';'
/// [!C99] init-declarator-list ';' [TODO: warn in c99 mode]
-/// [OMP] threadprivate-directive [TODO]
+/// [OMP] threadprivate-directive
+/// [OMP] allocate-directive [TODO]
///
Parser::DeclGroupPtrTy
Parser::ParseDeclOrFunctionDefInternal(ParsedAttributesWithRange &attrs,
explicit VarOrFuncDeclFilterCCC(Sema &S) : SemaRef(S) {}
bool ValidateCandidate(const TypoCorrection &Candidate) override {
NamedDecl *ND = Candidate.getCorrectionDecl();
- if (ND && (isa<VarDecl>(ND) || isa<FunctionDecl>(ND))) {
+ if (ND && ((isa<VarDecl>(ND) && ND->getKind() == Decl::Var) ||
+ isa<FunctionDecl>(ND))) {
return SemaRef.isDeclInScope(ND, SemaRef.getCurLexicalContext(),
SemaRef.getCurScope());
}
ExprResult Sema::ActOnOpenMPIdExpression(Scope *CurScope,
CXXScopeSpec &ScopeSpec,
- const DeclarationNameInfo &Id) {
+ const DeclarationNameInfo &Id,
+ OpenMPDirectiveKind Kind) {
LookupResult Lookup(*this, Id, LookupOrdinaryName);
LookupParsedName(Lookup, CurScope, &ScopeSpec, true);
// OpenMP [2.9.2, Syntax, C/C++]
// Variables must be file-scope, namespace-scope, or static block-scope.
- if (!VD->hasGlobalStorage()) {
+ if (Kind == OMPD_threadprivate && !VD->hasGlobalStorage()) {
Diag(Id.getLoc(), diag::err_omp_global_var_arg)
- << getOpenMPDirectiveName(OMPD_threadprivate) << !VD->isStaticLocal();
+ << getOpenMPDirectiveName(Kind) << !VD->isStaticLocal();
bool IsDecl =
VD->isThisDeclarationADefinition(Context) == VarDecl::DeclarationOnly;
Diag(VD->getLocation(),
if (CanonicalVD->getDeclContext()->isTranslationUnit() &&
!getCurLexicalContext()->isTranslationUnit()) {
Diag(Id.getLoc(), diag::err_omp_var_scope)
- << getOpenMPDirectiveName(OMPD_threadprivate) << VD;
+ << getOpenMPDirectiveName(Kind) << VD;
bool IsDecl =
VD->isThisDeclarationADefinition(Context) == VarDecl::DeclarationOnly;
Diag(VD->getLocation(),
if (CanonicalVD->isStaticDataMember() &&
!CanonicalVD->getDeclContext()->Equals(getCurLexicalContext())) {
Diag(Id.getLoc(), diag::err_omp_var_scope)
- << getOpenMPDirectiveName(OMPD_threadprivate) << VD;
+ << getOpenMPDirectiveName(Kind) << VD;
bool IsDecl =
VD->isThisDeclarationADefinition(Context) == VarDecl::DeclarationOnly;
Diag(VD->getLocation(),
(!getCurLexicalContext()->isFileContext() ||
!getCurLexicalContext()->Encloses(CanonicalVD->getDeclContext()))) {
Diag(Id.getLoc(), diag::err_omp_var_scope)
- << getOpenMPDirectiveName(OMPD_threadprivate) << VD;
+ << getOpenMPDirectiveName(Kind) << VD;
bool IsDecl =
VD->isThisDeclarationADefinition(Context) == VarDecl::DeclarationOnly;
Diag(VD->getLocation(),
// OpenMP [2.9.2, Restrictions, C/C++, p.6]
// A threadprivate directive for static block-scope variables must appear
// in the scope of the variable and not in a nested scope.
- if (CanonicalVD->isStaticLocal() && CurScope &&
+ if (CanonicalVD->isLocalVarDecl() && CurScope &&
!isDeclInScope(ND, getCurLexicalContext(), CurScope)) {
Diag(Id.getLoc(), diag::err_omp_var_scope)
- << getOpenMPDirectiveName(OMPD_threadprivate) << VD;
+ << getOpenMPDirectiveName(Kind) << VD;
bool IsDecl =
VD->isThisDeclarationADefinition(Context) == VarDecl::DeclarationOnly;
Diag(VD->getLocation(),
// OpenMP [2.9.2, Restrictions, C/C++, p.2-6]
// A threadprivate directive must lexically precede all references to any
// of the variables in its list.
- if (VD->isUsed() && !DSAStack->isThreadPrivate(VD)) {
+ if (Kind == OMPD_threadprivate && VD->isUsed() &&
+ !DSAStack->isThreadPrivate(VD)) {
Diag(Id.getLoc(), diag::err_omp_var_used)
- << getOpenMPDirectiveName(OMPD_threadprivate) << VD;
+ << getOpenMPDirectiveName(Kind) << VD;
return ExprError();
}
return D;
}
+Sema::DeclGroupPtrTy
+Sema::ActOnOpenMPAllocateDirective(SourceLocation Loc, ArrayRef<Expr *> VarList,
+ DeclContext *Owner) {
+ SmallVector<Expr *, 8> Vars;
+ for (Expr *RefExpr : VarList) {
+ auto *DE = cast<DeclRefExpr>(RefExpr);
+ auto *VD = cast<VarDecl>(DE->getDecl());
+
+ // Check if this is a TLS variable or global register.
+ if (VD->getTLSKind() != VarDecl::TLS_None ||
+ VD->hasAttr<OMPThreadPrivateDeclAttr>() ||
+ (VD->getStorageClass() == SC_Register && VD->hasAttr<AsmLabelAttr>() &&
+ !VD->isLocalVarDecl()))
+ continue;
+ // Do not apply for parameters.
+ if (isa<ParmVarDecl>(VD))
+ continue;
+
+ Vars.push_back(RefExpr);
+ VD->addAttr(
+ OMPAllocateDeclAttr::CreateImplicit(Context, DE->getSourceRange()));
+ if (ASTMutationListener *ML = Context.getASTMutationListener())
+ ML->DeclarationMarkedOpenMPAllocate(VD,
+ VD->getAttr<OMPAllocateDeclAttr>());
+ }
+ if (Vars.empty())
+ return nullptr;
+ if (!Owner)
+ Owner = getCurLexicalContext();
+ OMPAllocateDecl *D = OMPAllocateDecl::Create(Context, Owner, Loc, Vars);
+ D->setAccess(AS_public);
+ Owner->addDecl(D);
+ return DeclGroupPtrTy::make(DeclGroupRef(D));
+}
+
Sema::DeclGroupPtrTy
Sema::ActOnOpenMPRequiresDirective(SourceLocation Loc,
ArrayRef<OMPClause *> ClauseList) {
break;
}
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_taskyield:
case OMPD_barrier:
case OMPD_taskwait:
case OMPD_declare_target:
case OMPD_end_declare_target:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_declare_reduction:
case OMPD_declare_mapper:
case OMPD_declare_simd:
case OMPC_untied:
case OMPC_mergeable:
case OMPC_threadprivate:
+ case OMPC_allocate:
case OMPC_flush:
case OMPC_read:
case OMPC_write:
// Do not capture if-clause expressions.
break;
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_taskyield:
case OMPD_barrier:
case OMPD_taskwait:
case OMPD_taskloop:
case OMPD_taskloop_simd:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_taskyield:
case OMPD_barrier:
case OMPD_taskwait:
case OMPD_target_parallel_for:
case OMPD_target_parallel_for_simd:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_taskyield:
case OMPD_barrier:
case OMPD_taskwait:
case OMPD_target_parallel_for:
case OMPD_target_parallel_for_simd:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_taskyield:
case OMPD_barrier:
case OMPD_taskwait:
case OMPD_parallel:
case OMPD_parallel_sections:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_taskyield:
case OMPD_barrier:
case OMPD_taskwait:
case OMPD_parallel:
case OMPD_parallel_sections:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_taskyield:
case OMPD_barrier:
case OMPD_taskwait:
case OMPD_parallel_for:
case OMPD_parallel_for_simd:
case OMPD_threadprivate:
+ case OMPD_allocate:
case OMPD_taskyield:
case OMPD_barrier:
case OMPD_taskwait:
case OMPC_untied:
case OMPC_mergeable:
case OMPC_threadprivate:
+ case OMPC_allocate:
case OMPC_flush:
case OMPC_read:
case OMPC_write:
case OMPC_untied:
case OMPC_mergeable:
case OMPC_threadprivate:
+ case OMPC_allocate:
case OMPC_flush:
case OMPC_read:
case OMPC_write:
case OMPC_untied:
case OMPC_mergeable:
case OMPC_threadprivate:
+ case OMPC_allocate:
case OMPC_flush:
case OMPC_read:
case OMPC_write:
case OMPC_default:
case OMPC_proc_bind:
case OMPC_threadprivate:
+ case OMPC_allocate:
case OMPC_flush:
case OMPC_depend:
case OMPC_device:
case OMPC_untied:
case OMPC_mergeable:
case OMPC_threadprivate:
+ case OMPC_allocate:
case OMPC_read:
case OMPC_write:
case OMPC_update:
return TD;
}
+Decl *TemplateDeclInstantiator::VisitOMPAllocateDecl(OMPAllocateDecl *D) {
+ SmallVector<Expr *, 5> Vars;
+ for (auto *I : D->varlists()) {
+ Expr *Var = SemaRef.SubstExpr(I, TemplateArgs).get();
+ assert(isa<DeclRefExpr>(Var) && "allocate arg is not a DeclRefExpr");
+ Vars.push_back(Var);
+ }
+
+ Sema::DeclGroupPtrTy Res =
+ SemaRef.ActOnOpenMPAllocateDirective(D->getLocation(), Vars, Owner);
+ if (Res.get().isNull())
+ return nullptr;
+ return Res.get().getSingleDecl();
+}
+
Decl *TemplateDeclInstantiator::VisitOMPRequiresDecl(OMPRequiresDecl *D) {
llvm_unreachable(
"Requires directive cannot be instantiated within a dependent context");
case Decl::ClassScopeFunctionSpecialization:
case Decl::Import:
case Decl::OMPThreadPrivate:
+ case Decl::OMPAllocate:
case Decl::OMPRequires:
case Decl::OMPCapturedExpr:
case Decl::OMPDeclareReduction:
UPD_MANGLING_NUMBER,
UPD_STATIC_LOCAL_NUMBER,
UPD_DECL_MARKED_OPENMP_THREADPRIVATE,
+ UPD_DECL_MARKED_OPENMP_ALLOCATE,
UPD_DECL_MARKED_OPENMP_DECLARETARGET,
UPD_DECL_EXPORTED,
UPD_ADDED_ATTR_TO_RECORD
void VisitObjCPropertyDecl(ObjCPropertyDecl *D);
void VisitObjCPropertyImplDecl(ObjCPropertyImplDecl *D);
void VisitOMPThreadPrivateDecl(OMPThreadPrivateDecl *D);
+ void VisitOMPAllocateDecl(OMPAllocateDecl *D);
void VisitOMPDeclareReductionDecl(OMPDeclareReductionDecl *D);
void VisitOMPDeclareMapperDecl(OMPDeclareMapperDecl *D);
void VisitOMPRequiresDecl(OMPRequiresDecl *D);
D->setVars(Vars);
}
+void ASTDeclReader::VisitOMPAllocateDecl(OMPAllocateDecl *D) {
+ VisitDecl(D);
+ unsigned NumVars = D->varlist_size();
+ SmallVector<Expr *, 16> Vars;
+ Vars.reserve(NumVars);
+ for (unsigned i = 0; i != NumVars; ++i) {
+ Vars.push_back(Record.readExpr());
+ }
+ D->setVars(Vars);
+}
+
void ASTDeclReader::VisitOMPRequiresDecl(OMPRequiresDecl * D) {
VisitDecl(D);
unsigned NumClauses = D->clauselist_size();
isa<PragmaDetectMismatchDecl>(D))
return true;
if (isa<OMPThreadPrivateDecl>(D) || isa<OMPDeclareReductionDecl>(D) ||
- isa<OMPDeclareMapperDecl>(D))
+ isa<OMPDeclareMapperDecl>(D) || isa<OMPAllocateDecl>(D))
return !D->getDeclContext()->isFunctionOrMethod();
if (const auto *Var = dyn_cast<VarDecl>(D))
return Var->isFileVarDecl() &&
case DECL_OMP_THREADPRIVATE:
D = OMPThreadPrivateDecl::CreateDeserialized(Context, ID, Record.readInt());
break;
+ case DECL_OMP_ALLOCATE:
+ D = OMPAllocateDecl::CreateDeserialized(Context, ID, Record.readInt());
+ break;
case DECL_OMP_REQUIRES:
D = OMPRequiresDecl::CreateDeserialized(Context, ID, Record.readInt());
break;
ReadSourceRange()));
break;
+ case UPD_DECL_MARKED_OPENMP_ALLOCATE:
+ D->addAttr(OMPAllocateDeclAttr::CreateImplicit(Reader.getContext(),
+ ReadSourceRange()));
+ break;
+
case UPD_DECL_EXPORTED: {
unsigned SubmoduleID = readSubmoduleID();
auto *Exported = cast<NamedDecl>(D);
RECORD(DECL_PRAGMA_COMMENT);
RECORD(DECL_PRAGMA_DETECT_MISMATCH);
RECORD(DECL_OMP_DECLARE_REDUCTION);
+ RECORD(DECL_OMP_ALLOCATE);
// Statements and Exprs can occur in the Decls and Types block.
AddStmtsExprs(Stream, Record);
D->getAttr<OMPThreadPrivateDeclAttr>()->getRange());
break;
+ case UPD_DECL_MARKED_OPENMP_ALLOCATE:
+ Record.AddSourceRange(D->getAttr<OMPAllocateDeclAttr>()->getRange());
+ break;
+
case UPD_DECL_MARKED_OPENMP_DECLARETARGET:
Record.push_back(D->getAttr<OMPDeclareTargetDeclAttr>()->getMapType());
Record.AddSourceRange(
DeclUpdates[D].push_back(DeclUpdate(UPD_DECL_MARKED_OPENMP_THREADPRIVATE));
}
+void ASTWriter::DeclarationMarkedOpenMPAllocate(const Decl *D, const Attr *A) {
+ if (Chain && Chain->isProcessingUpdateRecords()) return;
+ assert(!WritingAST && "Already writing the AST!");
+ if (!D->isFromASTFile())
+ return;
+
+ DeclUpdates[D].push_back(DeclUpdate(UPD_DECL_MARKED_OPENMP_ALLOCATE, A));
+}
+
void ASTWriter::DeclarationMarkedOpenMPDeclareTarget(const Decl *D,
const Attr *Attr) {
if (Chain && Chain->isProcessingUpdateRecords()) return;
void VisitObjCPropertyDecl(ObjCPropertyDecl *D);
void VisitObjCPropertyImplDecl(ObjCPropertyImplDecl *D);
void VisitOMPThreadPrivateDecl(OMPThreadPrivateDecl *D);
+ void VisitOMPAllocateDecl(OMPAllocateDecl *D);
void VisitOMPRequiresDecl(OMPRequiresDecl *D);
void VisitOMPDeclareReductionDecl(OMPDeclareReductionDecl *D);
void VisitOMPDeclareMapperDecl(OMPDeclareMapperDecl *D);
Code = serialization::DECL_OMP_THREADPRIVATE;
}
+void ASTDeclWriter::VisitOMPAllocateDecl(OMPAllocateDecl *D) {
+ Record.push_back(D->varlist_size());
+ VisitDecl(D);
+ for (auto *I : D->varlists())
+ Record.AddStmt(I);
+ Code = serialization::DECL_OMP_ALLOCATE;
+}
+
void ASTDeclWriter::VisitOMPRequiresDecl(OMPRequiresDecl *D) {
Record.push_back(D->clauselist_size());
VisitDecl(D);
- OMPClauseWriter ClauseWriter(Record);
+ OMPClauseWriter ClauseWriter(Record);
for (OMPClause *C : D->clauselists())
ClauseWriter.writeClause(C);
Code = serialization::DECL_OMP_REQUIRES;
--- /dev/null
+// RUN: %clang_cc1 -verify -fopenmp -triple x86_64-apple-darwin10.6.0 -ast-print %s | FileCheck %s
+// RUN: %clang_cc1 -fopenmp -triple x86_64-apple-darwin10.6.0 -x c++ -std=c++11 -emit-pch -o %t %s
+// RUN: %clang_cc1 -fopenmp -triple x86_64-apple-darwin10.6.0 -std=c++11 -include-pch %t -fsyntax-only -verify %s -ast-print
+// RUN: %clang_cc1 -verify -fopenmp -triple x86_64-unknown-linux-gnu -ast-print %s | FileCheck %s
+// RUN: %clang_cc1 -fopenmp -fnoopenmp-use-tls -triple x86_64-unknown-linux-gnu -x c++ -std=c++11 -emit-pch -o %t %s
+// RUN: %clang_cc1 -fopenmp -fnoopenmp-use-tls -triple x86_64-unknown-linux-gnu -std=c++11 -include-pch %t -fsyntax-only -verify %s -ast-print
+
+// RUN: %clang_cc1 -verify -fopenmp-simd -triple x86_64-apple-darwin10.6.0 -ast-print %s | FileCheck %s
+// RUN: %clang_cc1 -fopenmp-simd -triple x86_64-apple-darwin10.6.0 -x c++ -std=c++11 -emit-pch -o %t %s
+// RUN: %clang_cc1 -fopenmp-simd -triple x86_64-apple-darwin10.6.0 -std=c++11 -include-pch %t -fsyntax-only -verify %s -ast-print
+// RUN: %clang_cc1 -verify -fopenmp-simd -triple x86_64-unknown-linux-gnu -ast-print %s | FileCheck %s
+// RUN: %clang_cc1 -fopenmp-simd -fnoopenmp-use-tls -triple x86_64-unknown-linux-gnu -x c++ -std=c++11 -emit-pch -o %t %s
+// RUN: %clang_cc1 -fopenmp-simd -fnoopenmp-use-tls -triple x86_64-unknown-linux-gnu -std=c++11 -include-pch %t -fsyntax-only -verify %s -ast-print
+// expected-no-diagnostics
+
+#ifndef HEADER
+#define HEADER
+
+struct St{
+ int a;
+};
+
+struct St1{
+ int a;
+ static int b;
+// CHECK: static int b;
+#pragma omp allocate(b)
+// CHECK-NEXT: #pragma omp allocate(St1::b){{$}}
+} d;
+
+int a, b;
+// CHECK: int a;
+// CHECK: int b;
+#pragma omp allocate(a)
+#pragma omp allocate(a)
+// CHECK-NEXT: #pragma omp allocate(a)
+// CHECK-NEXT: #pragma omp allocate(a)
+#pragma omp allocate(d, b)
+// CHECK-NEXT: #pragma omp allocate(d,b)
+
+template <class T>
+struct ST {
+ static T m;
+ #pragma omp allocate(m)
+};
+
+template <class T> T foo() {
+ T v;
+ #pragma omp allocate(v)
+ v = ST<T>::m;
+ return v;
+}
+//CHECK: template <class T> T foo() {
+//CHECK-NEXT: T v;
+//CHECK-NEXT: #pragma omp allocate(v)
+//CHECK: template<> int foo<int>() {
+//CHECK-NEXT: int v;
+//CHECK-NEXT: #pragma omp allocate(v)
+
+namespace ns{
+ int a;
+}
+// CHECK: namespace ns {
+// CHECK-NEXT: int a;
+// CHECK-NEXT: }
+#pragma omp allocate(ns::a)
+// CHECK-NEXT: #pragma omp allocate(ns::a)
+
+int main () {
+ static int a;
+// CHECK: static int a;
+#pragma omp allocate(a)
+// CHECK-NEXT: #pragma omp allocate(a)
+ a=2;
+ return (foo<int>());
+}
+
+extern template int ST<int>::m;
+#endif
--- /dev/null
+// RUN: %clang_cc1 -triple x86_64-apple-macos10.7.0 -verify -fopenmp -fnoopenmp-use-tls -ferror-limit 100 -emit-llvm -o - %s
+// RUN: %clang_cc1 -triple x86_64-apple-macos10.7.0 -verify -fopenmp -ferror-limit 100 -emit-llvm -o - %s
+
+// RUN: %clang_cc1 -triple x86_64-apple-macos10.7.0 -verify -fopenmp-simd -fnoopenmp-use-tls -ferror-limit 100 -emit-llvm -o - %s
+// RUN: %clang_cc1 -triple x86_64-apple-macos10.7.0 -verify -fopenmp-simd -ferror-limit 100 -emit-llvm -o - %s
+
+#pragma omp allocate // expected-error {{expected '(' after 'allocate'}}
+#pragma omp allocate( // expected-error {{expected identifier}} expected-error {{expected ')'}} expected-note {{to match this '('}}
+#pragma omp allocate() // expected-error {{expected identifier}}
+#pragma omp allocate(1) // expected-error {{expected unqualified-id}}
+struct CompleteSt {
+ int a;
+};
+
+struct CompleteSt1 {
+#pragma omp allocate(1) // expected-error {{expected unqualified-id}}
+ int a;
+} d; // expected-note {{'d' defined here}}
+
+int a; // expected-note {{'a' defined here}}
+
+#pragma omp allocate(a)
+#pragma omp allocate(u) // expected-error {{use of undeclared identifier 'u'}}
+#pragma omp allocate(d, a)
+int foo() { // expected-note {{declared here}}
+ static int l;
+#pragma omp allocate(l)) // expected-warning {{extra tokens at the end of '#pragma omp allocate' are ignored}}
+ return (a);
+}
+
+#pragma omp allocate(a)(
+// expected-warning@-1 {{extra tokens at the end of '#pragma omp allocate' are ignored}}
+#pragma omp allocate(a)[ // expected-warning {{extra tokens at the end of '#pragma omp allocate' are ignored}}
+#pragma omp allocate(a) { // expected-warning {{extra tokens at the end of '#pragma omp allocate' are ignored}}
+#pragma omp allocate(a)) // expected-warning {{extra tokens at the end of '#pragma omp allocate' are ignored}}
+#pragma omp allocate(a)] // expected-warning {{extra tokens at the end of '#pragma omp allocate' are ignored}}
+#pragma omp allocate(a) } // expected-warning {{extra tokens at the end of '#pragma omp allocate' are ignored}}
+#pragma omp allocate a // expected-error {{expected '(' after 'allocate'}}
+#pragma omp allocate(d // expected-error {{expected ')'}} expected-note {{to match this '('}}
+#pragma omp allocate(d)) // expected-warning {{extra tokens at the end of '#pragma omp allocate' are ignored}}
+int x, y;
+#pragma omp allocate(x)) // expected-warning {{extra tokens at the end of '#pragma omp allocate' are ignored}}
+#pragma omp allocate(y)),
+// expected-warning@-1 {{extra tokens at the end of '#pragma omp allocate' are ignored}}
+#pragma omp allocate(a, d)
+#pragma omp allocate(d.a) // expected-error {{expected identifier}}
+#pragma omp allocate((float)a) // expected-error {{expected unqualified-id}}
+int foa; // expected-note {{'foa' declared here}}
+#pragma omp allocate(faa) // expected-error {{use of undeclared identifier 'faa'; did you mean 'foa'?}}
+#pragma omp allocate(foo) // expected-error {{'foo' is not a global variable, static local variable or static data member}}
+#pragma omp allocate(int a = 2) // expected-error {{expected unqualified-id}}
+
+struct IncompleteSt;
+
+extern IncompleteSt e;
+#pragma omp allocate(e)
+
+int &f = a;
+#pragma omp allocate(f)
+
+class TestClass {
+private:
+ int a; // expected-note {{declared here}}
+ static int b; // expected-note {{'b' declared here}}
+ TestClass() : a(0) {}
+
+public:
+ TestClass(int aaa) : a(aaa) {}
+#pragma omp allocate(b, a) // expected-error {{'a' is not a global variable, static local variable or static data member}}
+} g(10);
+#pragma omp allocate(b) // expected-error {{use of undeclared identifier 'b'}}
+#pragma omp allocate(TestClass::b) // expected-error {{'#pragma omp allocate' must appear in the scope of the 'TestClass::b' variable declaration}}
+#pragma omp allocate(g)
+
+namespace ns {
+int m;
+#pragma omp allocate(m, m)
+} // namespace ns
+#pragma omp allocate(m) // expected-error {{use of undeclared identifier 'm'}}
+#pragma omp allocate(ns::m)
+#pragma omp allocate(ns \
+ : m) // expected-error {{unexpected ':' in nested name specifier; did you mean '::'?}}
+
+const int h = 12;
+const volatile int i = 10;
+#pragma omp allocate(h, i)
+
+template <class T>
+class TempClass {
+private:
+ T a;
+ TempClass() : a() {}
+
+public:
+ TempClass(T aaa) : a(aaa) {}
+ static T s;
+#pragma omp allocate(s)
+};
+#pragma omp allocate(s) // expected-error {{use of undeclared identifier 's'}}
+
+static __thread int t;
+#pragma omp allocate(t)
+
+// Register "0" is currently an invalid register for global register variables.
+// Use "esp" instead of "0".
+// register int reg0 __asm__("0");
+register int reg0 __asm__("esp");
+#pragma omp allocate(reg0)
+
+int o; // expected-note {{candidate found by name lookup is 'o'}}
+#pragma omp allocate(o)
+namespace {
+int o; // expected-note {{candidate found by name lookup is '(anonymous namespace)::o'}}
+#pragma omp allocate(o)
+#pragma omp allocate(o)
+} // namespace
+#pragma omp allocate(o) // expected-error {{reference to 'o' is ambiguous}}
+#pragma omp allocate(::o)
+
+int main(int argc, char **argv) {
+
+ int x, y = argc;
+ static double d1;
+ static double d2;
+ static double d3; // expected-note {{'d3' defined here}}
+ static double d4;
+ static TestClass LocalClass(y);
+#pragma omp allocate(LocalClass)
+
+ d.a = a;
+ d2++;
+ ;
+#pragma omp allocate(argc + y) // expected-error {{expected identifier}}
+#pragma omp allocate(argc, y)
+#pragma omp allocate(d2)
+#pragma omp allocate(d1)
+ {
+ ++a;
+ d2 = 0;
+#pragma omp allocate(d3) // expected-error {{'#pragma omp allocate' must appear in the scope of the 'd3' variable declaration}}
+ }
+#pragma omp allocate(d3)
+label:
+#pragma omp allocate(d4) // expected-error {{'#pragma omp allocate' cannot be an immediate substatement}}
+
+#pragma omp allocate(a) // expected-error {{'#pragma omp allocate' must appear in the scope of the 'a' variable declaration}}
+ return (y);
+#pragma omp allocate(d) // expected-error {{'#pragma omp allocate' must appear in the scope of the 'd' variable declaration}}
+}
--- /dev/null
+// no PCH
+// RUN: %clang_cc1 -fopenmp -fnoopenmp-use-tls -ast-print -include %s -include %s %s -o - | FileCheck %s
+// with PCH
+// RUN: %clang_cc1 -fopenmp -fnoopenmp-use-tls -ast-print -chain-include %s -chain-include %s %s -o - | FileCheck %s
+// no PCH
+// RUN: %clang_cc1 -fopenmp -ast-print -include %s -include %s %s -o - | FileCheck %s -check-prefix=CHECK-ALLOC-1
+// RUN: %clang_cc1 -fopenmp -ast-print -include %s -include %s %s -o - | FileCheck %s -check-prefix=CHECK-ALLOC-2
+// with PCH
+// RUN: %clang_cc1 -fopenmp -ast-print -chain-include %s -chain-include %s %s -o - | FileCheck %s -check-prefix=CHECK-ALLOC-1
+// RUN: %clang_cc1 -fopenmp -ast-print -chain-include %s -chain-include %s %s -o - | FileCheck %s -check-prefix=CHECK-ALLOC-2
+
+#if !defined(PASS1)
+#define PASS1
+
+int a;
+// CHECK: int a;
+
+#elif !defined(PASS2)
+#define PASS2
+
+#pragma omp allocate(a)
+// CHECK: #pragma omp allocate(a)
+
+#else
+
+// CHECK-LABEL: foo
+// CHECK-ALLOC-LABEL: foo
+int foo() {
+ return a;
+ // CHECK: return a;
+ // CHECK-ALLOC-1: return a;
+}
+
+// CHECK-ALLOC-2: return a;
+
+#endif
case Decl::CXXDeductionGuide:
case Decl::Import:
case Decl::OMPThreadPrivate:
+ case Decl::OMPAllocate:
case Decl::OMPDeclareReduction:
case Decl::OMPDeclareMapper:
case Decl::OMPRequires: