fraggamuffin created this revision.
fraggamuffin added a reviewer: cfe-commits.
fraggamuffin set the repository for this revision to rL LLVM.

Add parsing, sema analysis for 'declare target' construct for OpenMP 4.0.
Summary
The declare target directive specifies that variables, functions (C, C++ and
Fortran), and subroutines (Fortran) are mapped to a device. The declare target
directive is a declarative directive.

The syntax of the declare target directive is as follows:
C/C++
Fortran
The syntax of the declare target directive is as follows:

For variables, functions and subroutines:


```
#pragma omp declare target new-line
declarations-definition-seq
#pragma omp end declare target new-line
```

Codegen will be done in a separate delivery. This is based on the clang-omp 
github branch adapted for 3.8.
All unit tests passes (note that message test needed to add -fnoopenmp-use-tls 
to pass specifically the threadprivate part because use-tls is now set to 
default). All regression passes.
OpenMP 4.5 changes will be delivered separately.


Repository:
  rL LLVM

http://reviews.llvm.org/D15321

Files:
  include/clang/AST/DeclBase.h
  include/clang/AST/DeclOpenMP.h
  include/clang/AST/RecursiveASTVisitor.h
  include/clang/Basic/DeclNodes.td
  include/clang/Basic/DiagnosticParseKinds.td
  include/clang/Basic/DiagnosticSemaKinds.td
  include/clang/Basic/OpenMPKinds.def
  include/clang/Basic/OpenMPKinds.h
  include/clang/Parse/Parser.h
  include/clang/Sema/Sema.h
  include/clang/Serialization/ASTBitCodes.h
  lib/AST/ASTContext.cpp
  lib/AST/Decl.cpp
  lib/AST/DeclBase.cpp
  lib/AST/DeclOpenMP.cpp
  lib/AST/DeclPrinter.cpp
  lib/AST/ItaniumMangle.cpp
  lib/AST/MicrosoftMangle.cpp
  lib/Basic/OpenMPKinds.cpp
  lib/CodeGen/CGDecl.cpp
  lib/CodeGen/CodeGenModule.cpp
  lib/CodeGen/CodeGenModule.h
  lib/Parse/ParseDecl.cpp
  lib/Parse/ParseDeclCXX.cpp
  lib/Parse/ParseOpenMP.cpp
  lib/Parse/Parser.cpp
  lib/Sema/SemaDecl.cpp
  lib/Sema/SemaExpr.cpp
  lib/Sema/SemaLookup.cpp
  lib/Sema/SemaOpenMP.cpp
  lib/Sema/SemaTemplateInstantiate.cpp
  lib/Sema/SemaTemplateInstantiateDecl.cpp
  lib/Serialization/ASTCommon.cpp
  lib/Serialization/ASTReaderDecl.cpp
  lib/Serialization/ASTWriterDecl.cpp
  test/OpenMP/declare_target_ast_print.cpp
  test/OpenMP/declare_target_messages.cpp
  tools/libclang/CIndex.cpp

Index: tools/libclang/CIndex.cpp
===================================================================
--- tools/libclang/CIndex.cpp
+++ tools/libclang/CIndex.cpp
@@ -5228,6 +5228,7 @@
   case Decl::ClassScopeFunctionSpecialization:
   case Decl::Import:
   case Decl::OMPThreadPrivate:
+  case Decl::OMPDeclareTarget:
   case Decl::ObjCTypeParam:
   case Decl::BuiltinTemplate:
     return C;
Index: test/OpenMP/declare_target_messages.cpp
===================================================================
--- test/OpenMP/declare_target_messages.cpp
+++ test/OpenMP/declare_target_messages.cpp
@@ -0,0 +1,83 @@
+// RUN: %clang_cc1 -triple x86_64-apple-macos10.7.0 -verify -fopenmp -fnoopenmp-use-tls -ferror-limit 100 -o - %s
+
+#pragma omp end declare target // expected-error {{unexpected OpenMP directive '#pragma omp end declare target'}}
+
+int a, b; // expected-warning 2 {{declaration is not declared in any declare target region}}
+__thread int t; // expected-error {{threadprivate variables cannot be used in target constructs}}
+#pragma omp declare target private(a) // expected-warning {{extra tokens at the end of '#pragma omp declare target' are ignored}}
+void f();
+#pragma omp end declare target shared(a) // expected-warning {{extra tokens at the end of '#pragma omp end declare target' are ignored}}
+void c(); // expected-warning {{declaration is not declared in any declare target region}}
+
+extern int b;
+
+struct NonT {
+  int a;
+};
+
+typedef int sint;
+
+#pragma omp declare target // expected-note {{to match this '#pragma omp declare target'}}
+#pragma omp threadprivate(a) // expected-error {{threadprivate variables cannot be used in target constructs}} expected-note {{used here}}
+extern int b;
+int g;
+
+struct T { // expected-note {{mappable type cannot be polymorphic}}
+  int a;
+  virtual int method();
+};
+
+class VC { // expected-note {{mappable type cannot be polymorphic}}
+  T member;
+  NonT member1;
+  public:
+    virtual int method() { T a; return 0; } // expected-error {{type 'T' is not mappable to target}}
+};
+
+struct C {
+  NonT a;
+  sint b;
+  int method();
+  int method1();
+};
+
+int C::method1() {
+  return 0;
+}
+
+void foo() {
+  a = 0; // expected-note {{used here}}
+  b = 0; // expected-note {{used here}}
+  t = 1; // expected-note {{used here}}
+  C object;
+  VC object1; // expected-error {{type 'VC' is not mappable to target}}
+  g = object.method();
+  g += object.method1();
+  g += object1.method();
+  f();
+  c(); // expected-note {{used here}}
+}
+#pragma omp declare target // expected-error {{expected '#pragma omp end declare target'}}
+void foo1() {}
+#pragma omp end declare target
+#pragma omp end declare target // expected-error {{unexpected OpenMP directive '#pragma omp end declare target'}}
+
+int C::method() {
+  return 0;
+}
+
+struct S {
+#pragma omp declare target // expected-error {{directive must be at file or namespace scope}}
+  int v;
+#pragma omp end declare target // expected-error {{unexpected OpenMP directive '#pragma omp end declare target'}}
+};
+
+int main (int argc, char **argv) {
+#pragma omp declare target // expected-error {{unexpected OpenMP directive '#pragma omp declare target'}}
+  int v;
+#pragma omp end declare target // expected-error {{unexpected OpenMP directive '#pragma omp end declare target'}}
+  foo();
+  return (0);
+}
+
+#pragma omp declare target // expected-error {{expected '#pragma omp end declare target'}} expected-note {{to match this '#pragma omp declare target'}}
Index: test/OpenMP/declare_target_ast_print.cpp
===================================================================
--- test/OpenMP/declare_target_ast_print.cpp
+++ test/OpenMP/declare_target_ast_print.cpp
@@ -0,0 +1,47 @@
+// RUN: %clang_cc1 -verify -fopenmp -ast-print %s | FileCheck %s
+// RUN: %clang_cc1 -fopenmp -x c++ -std=c++11 -emit-pch -o %t %s
+// RUN: %clang_cc1 -fopenmp -std=c++11 -include-pch %t -fsyntax-only -verify %s -ast-print | FileCheck %s
+// expected-no-diagnostics
+
+#ifndef HEADER
+#define HEADER
+
+#pragma omp declare target
+// CHECK: #pragma omp declare target
+
+void foo() {}
+// CHECK-NEXT: void foo()
+
+#pragma omp end declare target
+// CHECK: #pragma omp end declare target
+
+extern "C" {
+#pragma omp declare target
+// CHECK: #pragma omp declare target
+
+void foo_c() {}
+// CHECK-NEXT: void foo_c()
+
+#pragma omp end declare target
+// CHECK: #pragma omp end declare target
+}
+
+extern "C++" {
+#pragma omp declare target
+// CHECK: #pragma omp declare target
+
+void foo_cpp() {}
+// CHECK-NEXT: void foo_cpp()
+
+#pragma omp end declare target
+// CHECK: #pragma omp end declare target
+}
+
+int main (int argc, char **argv) {
+  foo();
+  foo_c();
+  foo_cpp();
+  return (0);
+}
+
+#endif
Index: lib/Serialization/ASTWriterDecl.cpp
===================================================================
--- lib/Serialization/ASTWriterDecl.cpp
+++ lib/Serialization/ASTWriterDecl.cpp
@@ -131,6 +131,7 @@
     void VisitObjCPropertyDecl(ObjCPropertyDecl *D);
     void VisitObjCPropertyImplDecl(ObjCPropertyImplDecl *D);
     void VisitOMPThreadPrivateDecl(OMPThreadPrivateDecl *D);
+	void VisitOMPDeclareTargetDecl(OMPDeclareTargetDecl *D);
 
     /// Add an Objective-C type parameter list to the given record.
     void AddObjCTypeParamList(ObjCTypeParamList *typeParams) {
@@ -1617,6 +1618,11 @@
   Code = serialization::DECL_OMP_THREADPRIVATE;
 }
 
+void ASTDeclWriter::VisitOMPDeclareTargetDecl(OMPDeclareTargetDecl *D) {
+	VisitDecl(D);
+	Code = serialization::DECL_OMP_DECLARETARGET;
+}
+
 //===----------------------------------------------------------------------===//
 // ASTWriter Implementation
 //===----------------------------------------------------------------------===//
@@ -2071,8 +2077,8 @@
   // An ObjCMethodDecl is never considered as "required" because its
   // implementation container always is.
 
-  // File scoped assembly or obj-c implementation must be seen.
-  if (isa<FileScopeAsmDecl>(D) || isa<ObjCImplDecl>(D))
+  // File scoped assembly or obj-c or OMP Declare target implementation must be seen.
+  if (isa<FileScopeAsmDecl>(D) || isa<ObjCImplDecl>(D) || isa<OMPDeclareTargetDecl>(D))
     return true;
 
   // ImportDecl is used by codegen to determine the set of imported modules to
Index: lib/Serialization/ASTReaderDecl.cpp
===================================================================
--- lib/Serialization/ASTReaderDecl.cpp
+++ lib/Serialization/ASTReaderDecl.cpp
@@ -350,6 +350,7 @@
     void VisitObjCPropertyDecl(ObjCPropertyDecl *D);
     void VisitObjCPropertyImplDecl(ObjCPropertyImplDecl *D);
     void VisitOMPThreadPrivateDecl(OMPThreadPrivateDecl *D);
+	void VisitOMPDeclareTargetDecl(OMPDeclareTargetDecl *D);
 
     /// We've merged the definition \p MergedDef into the existing definition
     /// \p Def. Ensure that \p Def is made visible whenever \p MergedDef is made
@@ -2353,6 +2354,10 @@
   D->setVars(Vars);
 }
 
+void ASTDeclReader::VisitOMPDeclareTargetDecl(OMPDeclareTargetDecl *D) {
+	VisitDecl(D);
+}
+
 //===----------------------------------------------------------------------===//
 // Attribute Reading
 //===----------------------------------------------------------------------===//
@@ -2402,7 +2407,8 @@
       isa<ObjCProtocolDecl>(D) || 
       isa<ObjCImplDecl>(D) ||
       isa<ImportDecl>(D) ||
-      isa<OMPThreadPrivateDecl>(D))
+      isa<OMPThreadPrivateDecl>(D) ||
+	  isa<OMPDeclareTargetDecl>(D) )
     return true;
   if (VarDecl *Var = dyn_cast<VarDecl>(D))
     return Var->isFileVarDecl() &&
@@ -2721,7 +2727,7 @@
   if (needsAnonymousDeclarationNumber(New)) {
     setAnonymousDeclForMerging(Reader, New->getLexicalDeclContext(),
                                AnonymousDeclNumber, New);
-  } else if (DC->isTranslationUnit() && Reader.SemaObj &&
+  } else if (DC->isTranslationUnitOrDeclareTarget() && Reader.SemaObj &&
              !Reader.getContext().getLangOpts().CPlusPlus) {
     if (Reader.SemaObj->IdResolver.tryAddTopLevelDecl(New, Name))
       Reader.PendingFakeLookupResults[Name.getAsIdentifierInfo()]
@@ -2826,7 +2832,7 @@
       if (isSameEntity(Existing, D))
         return FindExistingResult(Reader, D, Existing, AnonymousDeclNumber,
                                   TypedefNameForLinkage);
-  } else if (DC->isTranslationUnit() && Reader.SemaObj &&
+  } else if (DC->isTranslationUnitOrDeclareTarget() && Reader.SemaObj &&
              !Reader.getContext().getLangOpts().CPlusPlus) {
     IdentifierResolver &IdResolver = Reader.SemaObj->IdResolver;
 
@@ -3298,6 +3304,9 @@
   case DECL_OMP_THREADPRIVATE:
     D = OMPThreadPrivateDecl::CreateDeserialized(Context, ID, Record[Idx++]);
     break;
+  case DECL_OMP_DECLARETARGET:
+	D = OMPDeclareTargetDecl::CreateDeserialized(Context, ID);
+	break;
   case DECL_EMPTY:
     D = EmptyDecl::CreateDeserialized(Context, ID);
     break;
Index: lib/Serialization/ASTCommon.cpp
===================================================================
--- lib/Serialization/ASTCommon.cpp
+++ lib/Serialization/ASTCommon.cpp
@@ -329,6 +329,7 @@
   case Decl::ClassScopeFunctionSpecialization:
   case Decl::Import:
   case Decl::OMPThreadPrivate:
+  case Decl::OMPDeclareTarget:
   case Decl::BuiltinTemplate:
     return false;
 
Index: lib/Sema/SemaTemplateInstantiateDecl.cpp
===================================================================
--- lib/Sema/SemaTemplateInstantiateDecl.cpp
+++ lib/Sema/SemaTemplateInstantiateDecl.cpp
@@ -2477,6 +2477,11 @@
   return TD;
 }
 
+Decl *
+TemplateDeclInstantiator::VisitOMPDeclareTargetDecl(OMPDeclareTargetDecl *D) {
+	llvm_unreachable("OpenMP declare target cannot be instantiated");
+}
+
 Decl *TemplateDeclInstantiator::VisitFunctionDecl(FunctionDecl *D) {
   return VisitFunctionDecl(D, nullptr);
 }
Index: lib/Sema/SemaTemplateInstantiate.cpp
===================================================================
--- lib/Sema/SemaTemplateInstantiate.cpp
+++ lib/Sema/SemaTemplateInstantiate.cpp
@@ -96,7 +96,7 @@
     // that will own this template template parameter. In this case, we
     // use empty template parameter lists for all of the outer templates
     // to avoid performing any substitutions.
-    if (Ctx->isTranslationUnit()) {
+    if (Ctx->isTranslationUnitOrDeclareTarget()) {
       if (TemplateTemplateParmDecl *TTP 
                                       = dyn_cast<TemplateTemplateParmDecl>(D)) {
         for (unsigned I = 0, N = TTP->getDepth() + 1; I != N; ++I)
Index: lib/Sema/SemaOpenMP.cpp
===================================================================
--- lib/Sema/SemaOpenMP.cpp
+++ lib/Sema/SemaOpenMP.cpp
@@ -138,6 +138,13 @@
 
   DSAVarData getDSA(StackTy::reverse_iterator Iter, VarDecl *D);
 
+  typedef llvm::DenseSet<Decl *> DeclaredTargetDeclsTy;
+
+  DeclaredTargetDeclsTy DeclaredTargetDecls;
+
+  OpenMPClauseKind getDSA(StackTy::reverse_iterator Iter, VarDecl *D,
+	  OpenMPDirectiveKind &Kind, DeclRefExpr *&E);
+
   /// \brief Checks if the variable is a local for OpenMP region.
   bool isOpenMPLocal(VarDecl *D, StackTy::reverse_iterator Iter);
 
@@ -163,6 +170,8 @@
     Stack.pop_back();
   }
 
+  bool IsThreadprivate(VarDecl *D, DeclRefExpr *&E);
+
   /// \brief If 'aligned' declaration for given variable \a D was not seen yet,
   /// add it and return NULL; otherwise return previous occurrence's expression
   /// for diagnostics.
@@ -289,6 +298,10 @@
     return Stack.back().CancelRegion;
   }
 
+  void addDeclareTargetDecl(Decl *D) { DeclaredTargetDecls.insert(D); }
+
+  bool isDeclareTargetDecl(Decl *D) { return DeclaredTargetDecls.count(D); }
+
   /// \brief Set collapse value for the region.
   void setCollapseNumber(unsigned Val) { Stack.back().CollapseNumber = Val; }
   /// \brief Return collapse value for region.
@@ -541,6 +554,17 @@
                              VK_LValue);
 }
 
+bool DSAStackTy::IsThreadprivate(VarDecl *D, DeclRefExpr *&E) {
+	E = 0;
+	if (D->getTLSKind() != VarDecl::TLS_None)
+		return true;
+	if (Stack[0].SharingMap.count(D)) {
+		E = Stack[0].SharingMap[D].RefExpr;
+		return true;
+	}
+	return false;
+}
+
 DSAStackTy::DSAVarData DSAStackTy::getTopDSA(VarDecl *D, bool FromParent) {
   D = D->getCanonicalDecl();
   DSAVarData DVar;
@@ -742,6 +766,13 @@
   VarDataSharingAttributesStack = new DSAStackTy(*this);
 }
 
+bool Sema::IsDeclContextInOpenMPTarget(DeclContext *DC) {
+	while (DC && !isa<OMPDeclareTargetDecl>(DC)) {
+		DC = DC->getParent();
+	}
+	return DC != 0;
+}
+
 #define DSAStack static_cast<DSAStackTy *>(VarDataSharingAttributesStack)
 
 bool Sema::IsOpenMPCapturedByRef(VarDecl *VD,
@@ -1036,8 +1067,10 @@
   // OpenMP [2.9.2, Restrictions, C/C++, p.2]
   //   A threadprivate directive for file-scope variables must appear outside
   //   any definition or declaration.
-  if (CanonicalVD->getDeclContext()->isTranslationUnit() &&
-      !getCurLexicalContext()->isTranslationUnit()) {
+
+	  if ((!getCurLexicalContext()->isFileContext() ||
+		  !VD->getDeclContext()->isFileContext()) &&
+		  !isDeclInScope(ND, getCurLexicalContext(), getCurScope())) {
     Diag(Id.getLoc(), diag::err_omp_var_scope)
         << getOpenMPDirectiveName(OMPD_threadprivate) << VD;
     bool IsDecl =
@@ -1103,7 +1136,8 @@
   }
 
   QualType ExprType = VD->getType().getNonReferenceType();
-  ExprResult DE = buildDeclRefExpr(*this, VD, ExprType, Id.getLoc());
+  //ExprResult DE = buildDeclRefExpr(*this, VD, ExprType, Id.getLoc());
+  ExprResult DE = BuildDeclRefExpr(VD, ExprType, VK_LValue, Id.getLoc());
   return DE;
 }
 
@@ -1223,6 +1257,221 @@
   return D;
 }
 
+bool Sema::ActOnStartOpenMPDeclareTargetDirective(Scope *S,
+	SourceLocation Loc) {
+	if (CurContext && !CurContext->isFileContext() &&
+		!CurContext->isExternCContext() && !CurContext->isExternCXXContext()) {
+		Diag(Loc, diag::err_omp_region_not_file_context);
+		return false;
+	}
+	OMPDeclareTargetDecl *DT =
+		OMPDeclareTargetDecl::Create(Context, CurContext, Loc);
+	DT->setAccess(AS_public);
+	CurContext->addDecl(DT);
+	if (CurScope)
+		PushDeclContext(S, DT);
+	else
+		CurContext = DT;
+	return true;
+}
+
+void Sema::ActOnOpenMPDeclareTargetDecls(Sema::DeclGroupPtrTy Decls) {
+	if (!Decls)
+		return;
+	DeclGroupRef DGR = Decls.get();
+	if (DGR.isNull())
+		return;
+	for (DeclGroupRef::iterator I = DGR.begin(), E = DGR.end(); I != E; ++I) {
+		if (*I)
+			DSAStack->addDeclareTargetDecl(*I);
+	}
+}
+
+Sema::DeclGroupPtrTy Sema::ActOnFinishOpenMPDeclareTargetDirective() {
+	if (CurContext && isa<OMPDeclareTargetDecl>(CurContext)) {
+		OMPDeclareTargetDecl *DT = cast<OMPDeclareTargetDecl>(CurContext);
+		PopDeclContext();
+		return DeclGroupPtrTy::make(DeclGroupRef(DT));
+	}
+	return DeclGroupPtrTy();
+}
+
+void Sema::ActOnOpenMPDeclareTargetDirectiveError() {
+	if (CurContext && isa<OMPDeclareTargetDecl>(CurContext)) {
+		PopDeclContext();
+	}
+}
+
+static bool IsCXXRecordForMappable(Sema &SemaRef, SourceLocation Loc,
+	DSAStackTy *Stack, CXXRecordDecl *RD) {
+	if (!RD || RD->isInvalidDecl())
+		return true;
+
+	QualType QTy = SemaRef.Context.getRecordType(RD);
+	if (RD->isDynamicClass()) {
+
+		SemaRef.Diag(Loc, diag::err_omp_not_mappable_type) << QTy;
+		SemaRef.Diag(RD->getLocation(), diag::note_omp_polymorphic_in_target);
+		return false;
+	}
+	DeclContext *DC = RD;
+	bool IsCorrect = true;
+	for (DeclContext::decl_iterator I = DC->noload_decls_begin(),
+		E = DC->noload_decls_end();
+		I != E; ++I) {
+		if (*I) {
+			if (CXXMethodDecl *MD = dyn_cast<CXXMethodDecl>(*I)) {
+				if (MD->isStatic()) {
+					SemaRef.Diag(Loc, diag::err_omp_not_mappable_type) << QTy;
+					SemaRef.Diag(MD->getLocation(),
+						diag::note_omp_static_member_in_target);
+					IsCorrect = false;
+				}
+			}
+			else if (VarDecl *VD = dyn_cast<VarDecl>(*I)) {
+				if (VD->isStaticDataMember()) {
+					SemaRef.Diag(Loc, diag::err_omp_not_mappable_type) << QTy;
+					SemaRef.Diag(VD->getLocation(),
+						diag::note_omp_static_member_in_target);
+					IsCorrect = false;
+				}
+			}
+		}
+	}
+	for (CXXRecordDecl::base_class_iterator I = RD->bases_begin(),
+		E = RD->bases_end();
+		I != E; ++I) {
+		if (!IsCXXRecordForMappable(SemaRef, I->getLocStart(), Stack,
+			I->getType()->getAsCXXRecordDecl())) {
+			IsCorrect = false;
+		}
+	}
+	return IsCorrect;
+}
+
+static void CheckDeclInTargetContext(SourceLocation SL, SourceRange SR,
+	Sema &SemaRef, DSAStackTy *Stack,
+	Decl *D) {
+	if (!D)
+		return;
+	Decl *LD = 0;
+	if (isa<TagDecl>(D)) {
+		LD = cast<TagDecl>(D)->getDefinition();
+	}
+	else if (isa<VarDecl>(D)) {
+		LD = cast<VarDecl>(D)->getDefinition();
+
+		// If this is an implicit variable that is legal and we do not need to do
+		// anything
+		if (cast<VarDecl>(D)->isImplicit()) {
+			Stack->addDeclareTargetDecl(D);
+			return;
+		}
+
+	}
+	else if (isa<FunctionDecl>(D)) {
+		const FunctionDecl *FD = 0;
+		if (cast<FunctionDecl>(D)->hasBody(FD))
+			LD = const_cast<FunctionDecl *>(FD);
+
+		// If the definition is associated with the current declaration in the
+		// target region (it can be e.g. a lambda) that is legal and we do not need
+		// to do anything else
+		if (LD == D) {
+			Stack->addDeclareTargetDecl(D);
+			return;
+		}
+	}
+	if (!LD)
+		LD = D;
+	if (LD) {
+		if (!Stack->isDeclareTargetDecl(LD)) {
+			// Outlined declaration is not declared target.
+			if (LD->isOutOfLine()) {
+				SemaRef.Diag(LD->getLocation(), diag::warn_omp_not_in_target_context);
+				SemaRef.Diag(SL, diag::note_used_here) << SR;
+			}
+			else {
+				DeclContext *DC = LD->getDeclContext();
+				while (DC) {
+					if (isa<OMPDeclareTargetDecl>(DC))
+						break;
+					DC = DC->getParent();
+				}
+				// Is not declared in target context.
+				if (!DC) {
+					SemaRef.Diag(LD->getLocation(), diag::warn_omp_not_in_target_context);
+					SemaRef.Diag(SL, diag::note_used_here) << SR;
+				}
+			}
+		}
+		// Mark decl as declared to prevent further diagnostic.
+		if (isa<VarDecl>(LD) || isa<FunctionDecl>(LD))
+			Stack->addDeclareTargetDecl(LD);
+	}
+}
+
+static bool IsCXXRecordForMappable(Sema &SemaRef, SourceLocation Loc,
+	DSAStackTy *Stack, CXXRecordDecl *RD);
+
+static bool CheckTypeMappable(SourceLocation SL, SourceRange SR, Sema &SemaRef,
+	DSAStackTy *Stack, QualType QTy) {
+	NamedDecl *ND;
+	if (QTy->isIncompleteType(&ND)) {
+		SemaRef.Diag(SL, diag::err_incomplete_type) << QTy << SR;
+		return false;
+	}
+	else if (CXXRecordDecl *RD = dyn_cast_or_null<CXXRecordDecl>(ND)) {
+		if (!RD->isInvalidDecl() &&
+			!IsCXXRecordForMappable(SemaRef, SL, Stack, RD)) {
+			return false;
+		}
+	}
+	return true;
+}
+
+static bool CheckValueDeclInTarget(SourceLocation SL, SourceRange SR,
+	Sema &SemaRef, DSAStackTy *Stack,
+	ValueDecl *VD) {
+	if (Stack->isDeclareTargetDecl(VD))
+		return true;
+	if (!CheckTypeMappable(SL, SR, SemaRef, Stack, VD->getType())) {
+		return false;
+	}
+	return true;
+}
+
+void Sema::CheckDeclIsAllowedInOpenMPTarget(Expr *E, Decl *D) {
+	if (!D || D->isInvalidDecl())
+		return;
+	SourceRange SR = E ? E->getSourceRange() : D->getSourceRange();
+	SourceLocation SL = E ? E->getLocStart() : D->getLocation();
+	if (VarDecl *VD = dyn_cast<VarDecl>(D)) {
+		DeclRefExpr *DRE;
+		if (DSAStack->IsThreadprivate(VD, DRE)) {
+			SourceLocation Loc = DRE ? DRE->getLocation() : VD->getLocation();
+			Diag(Loc, diag::err_omp_threadprivate_in_target);
+			Diag(SL, diag::note_used_here) << SR;
+			D->setInvalidDecl();
+			return;
+		}
+	}
+	if (ValueDecl *VD = dyn_cast<ValueDecl>(D)) {
+		if (!CheckValueDeclInTarget(SL, SR, *this, DSAStack, VD)) {
+			VD->setInvalidDecl();
+			return;
+		}
+	}
+	if (!E) {
+		// Checking declaration.
+		if (isa<VarDecl>(D) || isa<FunctionDecl>(D))
+			DSAStack->addDeclareTargetDecl(D);
+		return;
+	}
+	CheckDeclInTargetContext(E->getExprLoc(), E->getSourceRange(), *this,
+		DSAStack, D);
+}
+
 static void ReportOriginalDSA(Sema &SemaRef, DSAStackTy *Stack,
                               const VarDecl *VD, DSAStackTy::DSAVarData DVar,
                               bool IsLoopIterVar = false) {
@@ -7773,61 +8022,6 @@
   return new (Context) OMPDeviceClause(ValExpr, StartLoc, LParenLoc, EndLoc);
 }
 
-static bool IsCXXRecordForMappable(Sema &SemaRef, SourceLocation Loc,
-                                   DSAStackTy *Stack, CXXRecordDecl *RD) {
-  if (!RD || RD->isInvalidDecl())
-    return true;
-
-  auto QTy = SemaRef.Context.getRecordType(RD);
-  if (RD->isDynamicClass()) {
-    SemaRef.Diag(Loc, diag::err_omp_not_mappable_type) << QTy;
-    SemaRef.Diag(RD->getLocation(), diag::note_omp_polymorphic_in_target);
-    return false;
-  }
-  auto *DC = RD;
-  bool IsCorrect = true;
-  for (auto *I : DC->decls()) {
-    if (I) {
-      if (auto *MD = dyn_cast<CXXMethodDecl>(I)) {
-        if (MD->isStatic()) {
-          SemaRef.Diag(Loc, diag::err_omp_not_mappable_type) << QTy;
-          SemaRef.Diag(MD->getLocation(),
-                       diag::note_omp_static_member_in_target);
-          IsCorrect = false;
-        }
-      } else if (auto *VD = dyn_cast<VarDecl>(I)) {
-        if (VD->isStaticDataMember()) {
-          SemaRef.Diag(Loc, diag::err_omp_not_mappable_type) << QTy;
-          SemaRef.Diag(VD->getLocation(),
-                       diag::note_omp_static_member_in_target);
-          IsCorrect = false;
-        }
-      }
-    }
-  }
-
-  for (auto &I : RD->bases()) {
-    if (!IsCXXRecordForMappable(SemaRef, I.getLocStart(), Stack,
-                                I.getType()->getAsCXXRecordDecl()))
-      IsCorrect = false;
-  }
-  return IsCorrect;
-}
-
-static bool CheckTypeMappable(SourceLocation SL, SourceRange SR, Sema &SemaRef,
-                              DSAStackTy *Stack, QualType QTy) {
-  NamedDecl *ND;
-  if (QTy->isIncompleteType(&ND)) {
-    SemaRef.Diag(SL, diag::err_incomplete_type) << QTy << SR;
-    return false;
-  } else if (CXXRecordDecl *RD = dyn_cast_or_null<CXXRecordDecl>(ND)) {
-    if (!RD->isInvalidDecl() &&
-        !IsCXXRecordForMappable(SemaRef, SL, Stack, RD))
-      return false;
-  }
-  return true;
-}
-
 OMPClause *Sema::ActOnOpenMPMapClause(
     OpenMPMapClauseKind MapTypeModifier, OpenMPMapClauseKind MapType,
     SourceLocation MapLoc, SourceLocation ColonLoc, ArrayRef<Expr *> VarList,
Index: lib/Sema/SemaLookup.cpp
===================================================================
--- lib/Sema/SemaLookup.cpp
+++ lib/Sema/SemaLookup.cpp
@@ -828,7 +828,7 @@
     }
   }
 
-  if (!Found && DC->isTranslationUnit() && LookupBuiltin(S, R))
+  if (!Found && DC->isTranslationUnitOrDeclareTarget() && LookupBuiltin(S, R))
     return true;
 
   if (R.getLookupName().getNameKind()
Index: lib/Sema/SemaExpr.cpp
===================================================================
--- lib/Sema/SemaExpr.cpp
+++ lib/Sema/SemaExpr.cpp
@@ -13563,6 +13563,10 @@
 
 static void MarkExprReferenced(Sema &SemaRef, SourceLocation Loc,
                                Decl *D, Expr *E, bool OdrUse) {
+  if (SemaRef.IsDeclContextInOpenMPTarget(SemaRef.CurContext)) {
+	SemaRef.CheckDeclIsAllowedInOpenMPTarget(E, D);
+  }
+		
   if (VarDecl *Var = dyn_cast<VarDecl>(D)) {
     DoMarkVarDeclReferenced(SemaRef, Loc, Var, E);
     return;
Index: lib/Sema/SemaDecl.cpp
===================================================================
--- lib/Sema/SemaDecl.cpp
+++ lib/Sema/SemaDecl.cpp
@@ -4873,8 +4873,8 @@
               R->isFunctionType())) {
       IsLinkageLookup = true;
       CreateBuiltins =
-          CurContext->getEnclosingNamespaceContext()->isTranslationUnit();
-    } else if (CurContext->getRedeclContext()->isTranslationUnit() &&
+          CurContext->getEnclosingNamespaceContext()->isTranslationUnitOrDeclareTarget();
+    } else if (CurContext->getRedeclContext()->isTranslationUnitOrDeclareTarget() &&
                D.getDeclSpec().getStorageClassSpec() != DeclSpec::SCS_static)
       CreateBuiltins = true;
 
@@ -4990,6 +4990,10 @@
       CurContext->addHiddenDecl(New);
   }
 
+  if (IsDeclContextInOpenMPTarget(CurContext)) {
+	  CheckDeclIsAllowedInOpenMPTarget(0, New);
+  }
+
   return New;
 }
 
@@ -5118,7 +5122,7 @@
 void
 Sema::RegisterLocallyScopedExternCDecl(NamedDecl *ND, Scope *S) {
   if (!getLangOpts().CPlusPlus &&
-      ND->getLexicalDeclContext()->getRedeclContext()->isTranslationUnit())
+      ND->getLexicalDeclContext()->getRedeclContext()->isTranslationUnitOrDeclareTarget())
     // Don't need to track declarations in the TU in C.
     return;
 
@@ -5253,7 +5257,7 @@
   // If this is the C FILE type, notify the AST context.
   if (IdentifierInfo *II = NewTD->getIdentifier())
     if (!NewTD->isInvalidDecl() &&
-        NewTD->getDeclContext()->getRedeclContext()->isTranslationUnit()) {
+        NewTD->getDeclContext()->getRedeclContext()->isTranslationUnitOrDeclareTarget()) {
       if (II->isStr("FILE"))
         Context.setFILEDecl(NewTD);
       else if (II->isStr("jmp_buf"))
@@ -6454,7 +6458,7 @@
     // In C, when declaring a global variable, look for a corresponding 'extern'
     // variable declared in function scope. We don't need this in C++, because
     // we find local extern decls in the surrounding file-scope DeclContext.
-    if (ND->getDeclContext()->getRedeclContext()->isTranslationUnit()) {
+    if (ND->getDeclContext()->getRedeclContext()->isTranslationUnitOrDeclareTarget()) {
       if (NamedDecl *Prev = S.findLocallyScopedExternCDecl(ND->getDeclName())) {
         Previous.clear();
         Previous.addDecl(Prev);
@@ -6466,7 +6470,7 @@
 
   // A declaration in the translation unit can conflict with an extern "C"
   // declaration.
-  if (ND->getDeclContext()->getRedeclContext()->isTranslationUnit())
+  if (ND->getDeclContext()->getRedeclContext()->isTranslationUnitOrDeclareTarget())
     return checkGlobalOrExternCConflict(S, ND, /*IsGlobal*/true, Previous);
 
   // An extern "C" declaration can conflict with a declaration in the
@@ -8244,7 +8248,7 @@
   if (getLangOpts().CUDA)
     if (IdentifierInfo *II = NewFD->getIdentifier())
       if (!NewFD->isInvalidDecl() &&
-          NewFD->getDeclContext()->getRedeclContext()->isTranslationUnit()) {
+          NewFD->getDeclContext()->getRedeclContext()->isTranslationUnitOrDeclareTarget()) {
         if (II->isStr("cudaConfigureCall")) {
           if (!R->getAs<FunctionType>()->getReturnType()->isScalarType())
             Diag(NewFD->getLocation(), diag::err_config_scalar_return);
@@ -11462,7 +11466,7 @@
   if (!Name)
     return;
   if ((!getLangOpts().CPlusPlus &&
-       FD->getDeclContext()->isTranslationUnit()) ||
+       FD->getDeclContext()->isTranslationUnitOrDeclareTarget()) ||
       (isa<LinkageSpecDecl>(FD->getDeclContext()) &&
        cast<LinkageSpecDecl>(FD->getDeclContext())->getLanguage() ==
        LinkageSpecDecl::lang_c)) {
@@ -11737,7 +11741,7 @@
   // translation unit scope, at which point we have a fully qualified NNS.
   SmallVector<IdentifierInfo *, 4> Namespaces;
   DeclContext *DC = ND->getDeclContext()->getRedeclContext();
-  for (; !DC->isTranslationUnit(); DC = DC->getParent()) {
+  for (; !DC->isTranslationUnitOrDeclareTarget(); DC = DC->getParent()) {
     // This tag should be declared in a namespace, which can only be enclosed by
     // other namespaces.  Bail if there's an anonymous namespace in the chain.
     NamespaceDecl *Namespace = dyn_cast<NamespaceDecl>(DC);
@@ -11755,7 +11759,7 @@
   // build an NNS.
   SmallString<64> Insertion;
   llvm::raw_svector_ostream OS(Insertion);
-  if (DC->isTranslationUnit())
+  if (DC->isTranslationUnitOrDeclareTarget())
     OS << "::";
   std::reverse(Namespaces.begin(), Namespaces.end());
   for (auto *II : Namespaces)
@@ -12617,7 +12621,7 @@
   // If this is the C FILE type, notify the AST context.
   if (IdentifierInfo *II = New->getIdentifier())
     if (!New->isInvalidDecl() &&
-        New->getDeclContext()->getRedeclContext()->isTranslationUnit() &&
+        New->getDeclContext()->getRedeclContext()->isTranslationUnitOrDeclareTarget() &&
         II->isStr("FILE"))
       Context.setFILEDecl(New);
 
Index: lib/Parse/Parser.cpp
===================================================================
--- lib/Parse/Parser.cpp
+++ lib/Parse/Parser.cpp
@@ -658,7 +658,7 @@
     HandlePragmaOpenCLExtension();
     return DeclGroupPtrTy();
   case tok::annot_pragma_openmp:
-    return ParseOpenMPDeclarativeDirective();
+    return ParseOpenMPDeclarativeDirective(/*AS=*/AS_none);
   case tok::annot_pragma_ms_pointers_to_members:
     HandlePragmaMSPointersToMembers();
     return DeclGroupPtrTy();
@@ -1045,7 +1045,7 @@
            !TemplateInfo.TemplateParams &&
            (Tok.is(tok::l_brace) || Tok.is(tok::kw_try) ||
             Tok.is(tok::colon)) && 
-      Actions.CurContext->isTranslationUnit()) {
+      Actions.CurContext->isTranslationUnitOrDeclareTarget()) {
     ParseScope BodyScope(this, Scope::FnScope|Scope::DeclScope);
     Scope *ParentScope = getCurScope()->getParent();
 
Index: lib/Parse/ParseOpenMP.cpp
===================================================================
--- lib/Parse/ParseOpenMP.cpp
+++ lib/Parse/ParseOpenMP.cpp
@@ -32,13 +32,17 @@
   // TODO: add other combined directives in topological order.
   const OpenMPDirectiveKind F[][3] = {
       {OMPD_unknown /*cancellation*/, OMPD_unknown /*point*/,
-       OMPD_cancellation_point},
-      {OMPD_target, OMPD_unknown /*data*/, OMPD_target_data},
-      {OMPD_for, OMPD_simd, OMPD_for_simd},
-      {OMPD_parallel, OMPD_for, OMPD_parallel_for},
-      {OMPD_parallel_for, OMPD_simd, OMPD_parallel_for_simd},
-      {OMPD_parallel, OMPD_sections, OMPD_parallel_sections},
-      {OMPD_taskloop, OMPD_simd, OMPD_taskloop_simd}};
+       OMPD_cancellation_point},                                       //0
+	  {OMPD_unknown /*declare*/, OMPD_target /*target*/,
+	   OMPD_declare_target },                                          //1
+	  {OMPD_unknown /*end*/, OMPD_unknown /*declare*/,
+	   OMPD_end_declare_target },                                      //2
+      {OMPD_target, OMPD_unknown /*data*/, OMPD_target_data},          //3
+      {OMPD_for, OMPD_simd, OMPD_for_simd},                            //4
+      {OMPD_parallel, OMPD_for, OMPD_parallel_for},                    //5
+      {OMPD_parallel_for, OMPD_simd, OMPD_parallel_for_simd},          //6
+      {OMPD_parallel, OMPD_sections, OMPD_parallel_sections},          //7
+      {OMPD_taskloop, OMPD_simd, OMPD_taskloop_simd}};                 //8
   auto Tok = P.getCurToken();
   auto DKind =
       Tok.isAnnotation()
@@ -50,7 +54,13 @@
     if (!Tok.isAnnotation() && DKind == OMPD_unknown) {
       TokenMatched =
           (i == 0) &&
-          !P.getPreprocessor().getSpelling(Tok).compare("cancellation");
+           !P.getPreprocessor().getSpelling(Tok).compare("cancellation") ||
+		  ((i == 1 || i == 3) &&
+		   !P.getPreprocessor().getSpelling(Tok).compare("declare")) ||
+		  ((i == 2) &&
+		   !P.getPreprocessor().getSpelling(Tok).compare("end")) ||
+		  ((i == 3) && 
+		   !P.getPreprocessor().getSpelling(Tok).compare("target"));
     } else {
       TokenMatched = DKind == F[i][0] && DKind != OMPD_unknown;
     }
@@ -67,7 +77,10 @@
         TokenMatched =
             ((i == 0) &&
              !P.getPreprocessor().getSpelling(Tok).compare("point")) ||
-            ((i == 1) && !P.getPreprocessor().getSpelling(Tok).compare("data"));
+			((i == 2) &&
+			 !P.getPreprocessor().getSpelling(Tok).compare("declare")) ||
+			((i == 3) && 
+			 !P.getPreprocessor().getSpelling(Tok).compare("data"));
       } else {
         TokenMatched = SDKind == F[i][1] && SDKind != OMPD_unknown;
       }
@@ -86,7 +99,7 @@
 ///       threadprivate-directive:
 ///         annot_pragma_openmp 'threadprivate' simple-variable-list
 ///
-Parser::DeclGroupPtrTy Parser::ParseOpenMPDeclarativeDirective() {
+Parser::DeclGroupPtrTy Parser::ParseOpenMPDeclarativeDirective(AccessSpecifier AS) {
   assert(Tok.is(tok::annot_pragma_openmp) && "Not an OpenMP directive!");
   ParenBraceBracketBalancer BalancerRAIIObj(*this);
 
@@ -110,6 +123,59 @@
       return Actions.ActOnOpenMPThreadprivateDirective(Loc, Identifiers);
     }
     break;
+  case OMPD_declare_target: {
+	  SourceLocation DTLoc = ConsumeAnyToken();
+	  if (Tok.isNot(tok::annot_pragma_openmp_end)) {
+		  Diag(Tok, diag::warn_omp_extra_tokens_at_eol)
+			  << getOpenMPDirectiveName(OMPD_declare_target);
+		  while (!SkipUntil(tok::annot_pragma_openmp_end, StopBeforeMatch))
+			  ;
+	  }
+	  // Skip the last annot_pragma_openmp_end.
+	  ConsumeAnyToken();
+
+	  ParseScope OMPDeclareTargetScope(this, Scope::DeclScope);
+	  if (!Actions.ActOnStartOpenMPDeclareTargetDirective(getCurScope(), DTLoc))
+		  return DeclGroupPtrTy();
+
+	  DKind = ParseOpenMPDirectiveKind(*this);
+	  while (DKind != OMPD_end_declare_target && DKind != OMPD_declare_target &&
+		  Tok.isNot(tok::eof)) {
+		  ParsedAttributesWithRange attrs(AttrFactory);
+		  MaybeParseCXX11Attributes(attrs);
+		  MaybeParseMicrosoftAttributes(attrs);
+		  Actions.ActOnOpenMPDeclareTargetDecls(ParseExternalDeclaration(attrs));
+		  if (Tok.isAnnotation() && Tok.is(tok::annot_pragma_openmp)) {
+			  TentativeParsingAction TPA(*this);
+			  ConsumeToken();
+			  DKind = ParseOpenMPDirectiveKind(*this);
+			  if (DKind != OMPD_end_declare_target) {
+				  TPA.Revert();
+			  }
+			  else {
+				  TPA.Commit();
+			  }
+		  }
+	  }
+	  if (DKind == OMPD_end_declare_target) {
+		  // Skip the last annot_pragma_openmp_end.
+		  ConsumeAnyToken();
+		  ConsumeAnyToken();
+		  if (Tok.isNot(tok::annot_pragma_openmp_end)) {
+			  Diag(Tok, diag::warn_omp_extra_tokens_at_eol)
+				  << getOpenMPDirectiveName(OMPD_end_declare_target);
+			  while (!SkipUntil(tok::annot_pragma_openmp_end, StopBeforeMatch))
+				  ;
+		  }
+		  // Skip the last annot_pragma_openmp_end.
+		  ConsumeAnyToken();
+		  return Actions.ActOnFinishOpenMPDeclareTargetDirective();
+	  }
+	  Actions.ActOnOpenMPDeclareTargetDirectiveError();
+	  Diag(Tok, diag::err_expected_end_declare_target);
+	  Diag(DTLoc, diag::note_matching) << "'#pragma omp declare target'";
+	  return DeclGroupPtrTy();
+  }
   case OMPD_unknown:
     Diag(Tok, diag::err_omp_unknown_directive);
     break;
@@ -140,11 +206,13 @@
   case OMPD_target_data:
   case OMPD_taskloop:
   case OMPD_taskloop_simd:
+  default:
     Diag(Tok, diag::err_omp_unexpected_directive)
         << getOpenMPDirectiveName(DKind);
     break;
   }
-  SkipUntil(tok::annot_pragma_openmp_end);
+  while (!SkipUntil(tok::annot_pragma_openmp_end))
+	  ;
   return DeclGroupPtrTy();
 }
 
@@ -316,7 +384,14 @@
     Diag(Tok, diag::err_omp_unknown_directive);
     SkipUntil(tok::annot_pragma_openmp_end);
     break;
+  default:
+	  Diag(Tok, diag::err_omp_unexpected_directive)
+		  << getOpenMPDirectiveName(DKind);
+	  while (!SkipUntil(tok::annot_pragma_openmp_end))
+		  ;
+	  break;
   }
+
   return Directive;
 }
 
Index: lib/Parse/ParseDeclCXX.cpp
===================================================================
--- lib/Parse/ParseDeclCXX.cpp
+++ lib/Parse/ParseDeclCXX.cpp
@@ -2902,7 +2902,7 @@
   }
 
   if (Tok.is(tok::annot_pragma_openmp))
-    return ParseOpenMPDeclarativeDirective();
+    return ParseOpenMPDeclarativeDirective(AS);
 
   // Parse all the comma separated declarators.
   return ParseCXXClassMemberDeclaration(AS, AccessAttrs.getList());
Index: lib/Parse/ParseDecl.cpp
===================================================================
--- lib/Parse/ParseDecl.cpp
+++ lib/Parse/ParseDecl.cpp
@@ -3618,10 +3618,10 @@
 
     if (Tok.is(tok::annot_pragma_openmp)) {
       // Result can be ignored, because it must be always empty.
-      auto Res = ParseOpenMPDeclarativeDirective();
+      auto Res = ParseOpenMPDeclarativeDirective(AS_public);
       assert(!Res);
       // Silence possible warnings.
-      (void)Res;
+	  (void)Res;
       continue;
     }
     if (!Tok.is(tok::at)) {
Index: lib/CodeGen/CodeGenModule.h
===================================================================
--- lib/CodeGen/CodeGenModule.h
+++ lib/CodeGen/CodeGenModule.h
@@ -21,6 +21,7 @@
 #include "clang/AST/Attr.h"
 #include "clang/AST/DeclCXX.h"
 #include "clang/AST/DeclObjC.h"
+#include "clang/AST/DeclOpenMP.h"
 #include "clang/AST/GlobalDecl.h"
 #include "clang/AST/Mangle.h"
 #include "clang/Basic/ABI.h"
@@ -1063,6 +1064,236 @@
     DeferredVTables.push_back(RD);
   }
 
+  class OpenMPSupportStackTy {
+	  /// \brief A set of OpenMP threadprivate variables.
+	  llvm::DenseMap<const Decl *, const Expr *> OpenMPThreadPrivate;
+	  /// \brief A set of OpenMP private variables.
+	  typedef llvm::DenseMap<const Decl *, llvm::Value *> OMPPrivateVarsTy;
+	  struct OMPStackElemTy {
+		  OMPPrivateVarsTy PrivateVars;
+		  llvm::BasicBlock *IfEnd;
+		  Expr *IfClauseCondition;
+		  llvm::SmallVector<llvm::Value *, 16> offloadingMapArguments;
+		  llvm::Function *ReductionFunc;
+		  CodeGenModule &CGM;
+		  CodeGenFunction *RedCGF;
+		  llvm::SmallVector<llvm::Type *, 16> ReductionTypes;
+		  llvm::DenseMap<const VarDecl *, unsigned> ReductionMap;
+		  llvm::StructType *ReductionRec;
+		  llvm::Value *ReductionRecVar;
+		  llvm::Value *RedArg1;
+		  llvm::Value *RedArg2;
+		  llvm::Value *ReduceSwitch;
+		  llvm::BasicBlock *BB1;
+		  llvm::Instruction *BB1IP;
+		  llvm::BasicBlock *BB2;
+		  llvm::Instruction *BB2IP;
+		  llvm::Value *LockVar;
+		  llvm::BasicBlock *LastprivateBB;
+		  llvm::Instruction *LastprivateIP;
+		  llvm::BasicBlock *LastprivateEndBB;
+		  llvm::Value *LastIterVar;
+		  llvm::Value *TaskFlags;
+		  llvm::Value *PTaskTValue;
+		  llvm::Value *PTask;
+		  llvm::Value *UntiedPartIdAddr;
+		  unsigned     UntiedCounter;
+		  llvm::Value *UntiedSwitch;
+		  llvm::BasicBlock *UntiedEnd;
+		  CodeGenFunction *ParentCGF;
+		  bool NoWait;
+		  bool Mergeable;
+		  bool Ordered;
+		  int Schedule;
+		  const Expr *ChunkSize;
+		  bool NewTask;
+		  bool Untied;
+		  bool TargetDeclare;
+		  bool Target;
+		  bool HasLastPrivate;
+		  bool Distribute;
+		  llvm::DenseMap<const ValueDecl *, FieldDecl *> TaskFields;
+		  llvm::Type *TaskPrivateTy;
+		  QualType TaskPrivateQTy;
+		  llvm::Value *TaskPrivateBase;
+		  Expr *NumTeams;
+		  Expr *ThreadLimit;
+		  llvm::Value **WaitDepsArgs;
+		  llvm::SmallVector<const Expr *, 8> OffloadingMapDecls;
+		  llvm::SmallVector<llvm::Value *, 8> OffloadingMapBasePtrs;
+		  llvm::SmallVector<llvm::Value *, 8> OffloadingMapPtrs;
+		  llvm::SmallVector<llvm::Value *, 8> OffloadingMapSizes;
+		  llvm::SmallVector<unsigned, 8> OffloadingMapTypes;
+		  bool MapsBegin;
+		  bool MapsEnd;
+		  llvm::CallInst* OffloadingMapBeginFunctionCall;
+		  llvm::Value* OffloadingDevice;
+		  llvm::CallInst* OffloadingHostFunctionCall;
+		  OMPStackElemTy(CodeGenModule &CGM);
+		  ~OMPStackElemTy();
+	  };
+	  typedef llvm::SmallVector<OMPStackElemTy, 16> OMPStackTy;
+	  OMPStackTy OpenMPStack;
+	  CodeGenModule &CGM;
+	  llvm::Type *KMPDependInfoType;
+	  unsigned KMPDependInfoTypeAlign;
+  public:
+	  OpenMPSupportStackTy(CodeGenModule &CGM)
+		  : OpenMPThreadPrivate(), OpenMPStack(), CGM(CGM), KMPDependInfoType(0) { }
+	  bool isEmpty() { return OpenMPStack.empty(); }
+	  const Expr *hasThreadPrivateVar(const VarDecl *VD) {
+		  const VarDecl *RVD = VD->getMostRecentDecl();
+		  while (RVD) {
+			  llvm::DenseMap<const Decl *, const Expr *>::iterator I =
+				  OpenMPThreadPrivate.find(RVD);
+			  if (I != OpenMPThreadPrivate.end())
+				  return I->second;
+			  RVD = RVD->getPreviousDecl();
+		  }
+		  return 0;
+	  }
+	  void addThreadPrivateVar(const VarDecl *VD, const Expr *TPE) {
+		  OpenMPThreadPrivate[VD] = TPE;
+	  }
+	  /// \brief Checks, if the specified variable is currently marked as
+	  /// private.
+	  /// \return 0 if the variable is not private, or address of private
+	  /// otherwise.
+	  llvm::Value *getOpenMPPrivateVar(const VarDecl *VD) {
+		  if (OpenMPStack.empty()) return 0;
+		  for (OMPStackTy::reverse_iterator I = OpenMPStack.rbegin(),
+			  E = OpenMPStack.rend();
+			  I != E; ++I) {
+			  if (I->PrivateVars.count(VD) > 0 && I->PrivateVars[VD])
+				  return I->PrivateVars[VD];
+			  if (I->NewTask) return 0;
+		  }
+		  return 0;
+	  }
+	  llvm::Value *getTopOpenMPPrivateVar(const VarDecl *VD) {
+		  if (OpenMPStack.empty()) return 0;
+		  return OpenMPStack.back().PrivateVars.count(VD) > 0 ? OpenMPStack.back().PrivateVars[VD] : 0;
+	  }
+	  llvm::Value *getPrevOpenMPPrivateVar(const VarDecl *VD) {
+		  if (OpenMPStack.size()< 2) return 0;
+		  return OpenMPStack[OpenMPStack.size() - 2].PrivateVars.count(VD) > 0 ? OpenMPStack[OpenMPStack.size() - 2].PrivateVars[VD] : 0;
+	  }
+	  void startOpenMPRegion(bool NewTask) {
+		  OpenMPStack.push_back(OMPStackElemTy(CGM));
+		  OpenMPStack.back().NewTask = NewTask;
+	  }
+	  bool isNewTask() { return OpenMPStack.back().NewTask; };
+	  void endOpenMPRegion();
+	  void addOpenMPPrivateVar(const VarDecl *VD, llvm::Value *Addr) {
+		  assert(!OpenMPStack.empty() &&
+			  "OpenMP private variables region is not started.");
+		  OpenMPStack.back().PrivateVars[VD] = Addr;
+	  }
+	  void delOpenMPPrivateVar(const VarDecl *VD) {
+		  assert(!OpenMPStack.empty() &&
+			  "OpenMP private variables region is not started.");
+		  OpenMPStack.back().PrivateVars[VD] = 0;
+	  }
+	  void delPrevOpenMPPrivateVar(const VarDecl *VD) {
+		  assert(OpenMPStack.size() >= 2 &&
+			  "OpenMP private variables region is not started.");
+		  OpenMPStack[OpenMPStack.size() - 2].PrivateVars[VD] = 0;
+	  }
+	  void setIfDest(llvm::BasicBlock *EndBB) { OpenMPStack.back().IfEnd = EndBB; }
+	  llvm::BasicBlock *takeIfDest() {
+		  llvm::BasicBlock *BB = OpenMPStack.back().IfEnd;
+		  OpenMPStack.back().IfEnd = 0;
+		  return BB;
+	  }
+	  void setIfClauseCondition(Expr *IfClauseCondition) {
+		  OpenMPStack.back().IfClauseCondition = IfClauseCondition;
+	  }
+	  void resetIfClauseCondition() {
+		  OpenMPStack.back().IfClauseCondition = nullptr;
+	  }
+	  Expr *getIfClauseCondition() {
+		  return OpenMPStack.back().IfClauseCondition;
+	  }
+	  CodeGenFunction &getCGFForReductionFunction();
+	  void getReductionFunctionArgs(llvm::Value *&Arg1, llvm::Value *&Arg2);
+	  void registerReductionVar(const VarDecl *VD, llvm::Type *Type);
+	  llvm::Value *getReductionRecVar(CodeGenFunction &CGF);
+	  llvm::Type *getReductionRec();
+	  llvm::Value *getReductionSwitch();
+	  void setReductionSwitch(llvm::Value *Switch);
+	  void setReductionIPs(llvm::BasicBlock *BB1, llvm::Instruction *IP1,
+		  llvm::BasicBlock *BB2, llvm::Instruction *IP2);
+	  void getReductionIPs(llvm::BasicBlock *&BB1, llvm::Instruction *&IP1,
+		  llvm::BasicBlock *&BB2, llvm::Instruction *&IP2);
+	  llvm::Value *getReductionLockVar();
+	  void setReductionLockVar(llvm::Value *Var);
+	  void setLastprivateIP(llvm::BasicBlock *BB, llvm::Instruction *IP, llvm::BasicBlock *EndBB);
+	  void getLastprivateIP(llvm::BasicBlock *&BB, llvm::Instruction *&IP, llvm::BasicBlock *&EndBB);
+	  llvm::Value *getLastIterVar();
+	  void setLastIterVar(llvm::Value *Var);
+	  unsigned getReductionVarIdx(const VarDecl *VD);
+	  unsigned getNumberOfReductionVars();
+	  void setNoWait(bool Flag);
+	  bool getNoWait();
+	  void setScheduleChunkSize(int Sched, const Expr *Size);
+	  void getScheduleChunkSize(int &Sched, const Expr *&Size);
+	  void setMergeable(bool Flag);
+	  bool getMergeable();
+	  void setOrdered(bool Flag);
+	  bool getOrdered();
+	  void setUntied(bool Flag);
+	  bool getUntied();
+	  void setTargetDeclare(bool Flag);
+	  bool getTargetDeclare();
+	  void setTarget(bool Flag);
+	  bool getTarget();
+	  void setDistribute(bool Flag);
+	  bool getDistribute();
+	  bool getParentUntied();
+	  void setHasLastPrivate(bool Flag);
+	  bool hasLastPrivate();
+	  llvm::Value *getTaskFlags();
+	  void setTaskFlags(llvm::Value *Flags);
+	  void setPTask(llvm::Value *Task, llvm::Value *TaskT, llvm::Type *PTy, QualType PQTy, llvm::Value *PB);
+	  void getPTask(llvm::Value *&Task, llvm::Value *&TaskT, llvm::Type *&PTy, QualType &PQTy, llvm::Value *&PB);
+	  llvm::DenseMap<const ValueDecl *, FieldDecl *> &getTaskFields();
+	  void setUntiedData(llvm::Value *UntiedPartIdAddr, llvm::Value *UntiedSwitch, llvm::BasicBlock *UntiedEnd, unsigned UntiedCounter, CodeGenFunction *CGF);
+	  void getUntiedData(llvm::Value *&UntiedPartIdAddr, llvm::Value *&UntiedSwitch, llvm::BasicBlock *&UntiedEnd, unsigned &UntiedCounter);
+	  void setParentUntiedData(llvm::Value *UntiedPartIdAddr, llvm::Value *UntiedSwitch, llvm::BasicBlock *UntiedEnd, unsigned UntiedCounter, CodeGenFunction *CGF);
+	  void getParentUntiedData(llvm::Value *&UntiedPartIdAddr, llvm::Value *&UntiedSwitch, llvm::BasicBlock *&UntiedEnd, unsigned &UntiedCounter, CodeGenFunction *&CGF);
+	  void setKMPDependInfoType(llvm::Type *Ty, unsigned Align) { KMPDependInfoType = Ty; KMPDependInfoTypeAlign = Align; }
+	  llvm::Type *getKMPDependInfoType() { return KMPDependInfoType; }
+	  unsigned getKMPDependInfoTypeAlign() { return KMPDependInfoTypeAlign; }
+	  void setNumTeams(Expr *Num);
+	  void setThreadLimit(Expr *Num);
+	  Expr *getNumTeams();
+	  Expr *getThreadLimit();
+	  void setWaitDepsArgs(llvm::Value **Args);
+	  llvm::Value **getWaitDepsArgs();
+	  void addOffloadingMap(const Expr *DExpr, llvm::Value *BasePtr, llvm::Value *Ptr, llvm::Value *Size, unsigned Type);
+	  void getOffloadingMapArrays(ArrayRef<const Expr*> &DExprs, ArrayRef<llvm::Value*> &BasePtrs, ArrayRef<llvm::Value*> &Ptrs, ArrayRef<llvm::Value*> &Sizes, ArrayRef<unsigned> &Types);
+	  llvm::CallInst*  getOffloadingMapBeginFunctionCall();
+	  void setOffloadingMapBeginFunctionCall(llvm::CallInst *OffloadingMapBeginFunctionCall);
+	  void setOffloadingMapArguments(llvm::ArrayRef<llvm::Value *> Args) {
+		  for (auto Arg : Args) {
+			  OpenMPStack.back().offloadingMapArguments.push_back(Arg);
+		  }
+	  }
+	  llvm::SmallVector<llvm::Value *, 16> &getOffloadingMapArguments() {
+		  return OpenMPStack.back().offloadingMapArguments;
+	  }
+	  void setMapsBegin(bool Flag);
+	  bool getMapsBegin();
+	  void setMapsEnd(bool Flag);
+	  bool getMapsEnd();
+	  void setOffloadingDevice(llvm::Value *device);
+	  llvm::Value* getOffloadingDevice();
+	  void setOffloadingHostFunctionCall(llvm::CallInst *OffloadingHostFunctionCall);
+	  llvm::CallInst* getOffloadingHostFunctionCall();
+  };
+
+  OpenMPSupportStackTy OpenMPSupport;
+
   /// Emit code for a singal global function or var decl. Forward declarations
   /// are emitted lazily.
   void EmitGlobal(GlobalDecl D);
@@ -1097,6 +1328,10 @@
   /// \param D Threadprivate declaration.
   void EmitOMPThreadPrivateDecl(const OMPThreadPrivateDecl *D);
 
+  /// \brief Emit declare target decls.
+  ///
+  void EmitOMPDeclareTarget(const OMPDeclareTargetDecl *D);
+
   /// Returns whether the given record is blacklisted from control flow
   /// integrity checks.
   bool IsCFIBlacklistedRecord(const CXXRecordDecl *RD);
Index: lib/CodeGen/CodeGenModule.cpp
===================================================================
--- lib/CodeGen/CodeGenModule.cpp
+++ lib/CodeGen/CodeGenModule.cpp
@@ -95,7 +95,8 @@
       NSConcreteStackBlock(nullptr), BlockObjectAssign(nullptr),
       BlockObjectDispose(nullptr), BlockDescriptorType(nullptr),
       GenericBlockLiteralType(nullptr), LifetimeStartFn(nullptr),
-      LifetimeEndFn(nullptr), SanitizerMD(new SanitizerMetadata(*this)) {
+      LifetimeEndFn(nullptr), SanitizerMD(new SanitizerMetadata(*this)), 
+	  OpenMPSupport(*this) {
 
   // Initialize the type cache.
   llvm::LLVMContext &LLVMContext = M.getContext();
@@ -3567,6 +3568,10 @@
     break;
   }
 
+  case Decl::OMPDeclareTarget:
+	  EmitOMPDeclareTarget(cast<OMPDeclareTargetDecl>(D));
+	  break;
+
   default:
     // Make sure we handled everything we should, every other kind is a
     // non-top-level decl.  FIXME: Would be nice to have an isTopLevelDeclKind
@@ -3869,6 +3874,440 @@
   return InternalId;
 }
 
+CodeGenModule::OpenMPSupportStackTy::OMPStackElemTy::OMPStackElemTy(CodeGenModule &CGM)
+	: PrivateVars(), IfEnd(0), IfClauseCondition(0), ReductionFunc(0), CGM(CGM),
+	RedCGF(0), ReductionTypes(), ReductionMap(), ReductionRec(0), ReductionRecVar(0),
+	RedArg1(0), RedArg2(0), ReduceSwitch(0), BB1(0), BB1IP(0), BB2(0), BB2IP(0), LockVar(0),
+	LastprivateBB(0), LastprivateIP(0), LastprivateEndBB(0), LastIterVar(0), TaskFlags(0),
+	PTaskTValue(0), PTask(0), UntiedPartIdAddr(0), UntiedCounter(0), UntiedSwitch(0),
+	UntiedEnd(0), ParentCGF(0),
+	NoWait(true), Mergeable(false), Schedule(0), ChunkSize(0), NewTask(false),
+	Untied(false), HasLastPrivate(false),
+	TaskPrivateTy(0), TaskPrivateQTy(), TaskPrivateBase(0), NumTeams(0), ThreadLimit(0),
+	WaitDepsArgs(0), MapsBegin(0), MapsEnd(0),
+	OffloadingMapBeginFunctionCall(0), OffloadingDevice(0),
+	OffloadingHostFunctionCall(0) { }
+
+CodeGenFunction &CodeGenModule::OpenMPSupportStackTy::getCGFForReductionFunction() {
+	if (!OpenMPStack.back().RedCGF) {
+		OpenMPStack.back().RedCGF = new CodeGenFunction(CGM, true);
+		OpenMPStack.back().RedCGF->CurFn = 0;
+	}
+	return *OpenMPStack.back().RedCGF;
+}
+
+CodeGenModule::OpenMPSupportStackTy::OMPStackElemTy::~OMPStackElemTy() {
+	if (RedCGF) delete RedCGF;
+	RedCGF = 0;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::endOpenMPRegion() {
+	assert(!OpenMPStack.empty() &&
+		"OpenMP private variables region is not started.");
+	assert(!OpenMPStack.back().IfEnd && "If not closed.");
+	OpenMPStack.pop_back();
+}
+
+void CodeGenModule::OpenMPSupportStackTy::registerReductionVar(
+	const VarDecl *VD,
+	llvm::Type *Type) {
+	OpenMPStack.back().ReductionMap[VD] =
+		OpenMPStack.back().ReductionTypes.size();
+	OpenMPStack.back().ReductionTypes.push_back(Type);
+}
+
+llvm::Value *
+CodeGenModule::OpenMPSupportStackTy::getReductionRecVar(CodeGenFunction &CGF) {
+	if (!OpenMPStack.back().ReductionRecVar) {
+		OpenMPStack.back().ReductionRec =
+			llvm::StructType::get(CGM.getLLVMContext(),
+				OpenMPStack.back().ReductionTypes);
+		llvm::AllocaInst *AI = CGF.CreateTempAlloca(OpenMPStack.back().ReductionRec,
+			"reduction.rec.var");
+		AI->setAlignment(CGF.CGM.PointerAlignInBytes);
+		OpenMPStack.back().ReductionRecVar = AI;
+	}
+	return OpenMPStack.back().ReductionRecVar;
+}
+
+llvm::Type *
+CodeGenModule::OpenMPSupportStackTy::getReductionRec() {
+	assert(OpenMPStack.back().ReductionRec &&
+		"Type is not defined.");
+	return OpenMPStack.back().ReductionRec;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::getReductionFunctionArgs(
+	llvm::Value *&Arg1, llvm::Value *&Arg2) {
+	assert(OpenMPStack.back().RedCGF && OpenMPStack.back().RedCGF->CurFn &&
+		"Reduction function is closed.");
+	if (!OpenMPStack.back().RedArg1 && !OpenMPStack.back().RedArg2) {
+		CodeGenFunction &CGF = *OpenMPStack.back().RedCGF;
+		llvm::Value *Arg1 = &CGF.CurFn->getArgumentList().front();
+		llvm::Value *Arg2 = &CGF.CurFn->getArgumentList().back();
+		llvm::Type *PtrTy = OpenMPStack.back().ReductionRec->getPointerTo();
+		OpenMPStack.back().RedArg1 = CGF.Builder.CreateBitCast(Arg1, PtrTy,
+			"reduction.lhs");
+		OpenMPStack.back().RedArg2 = CGF.Builder.CreateBitCast(Arg2, PtrTy,
+			"reduction.rhs");
+	}
+	Arg1 = OpenMPStack.back().RedArg1;
+	Arg2 = OpenMPStack.back().RedArg2;
+}
+
+unsigned
+CodeGenModule::OpenMPSupportStackTy::getReductionVarIdx(const VarDecl *VD) {
+	assert(OpenMPStack.back().ReductionMap.count(VD) > 0 && "No reduction var.");
+	return OpenMPStack.back().ReductionMap[VD];
+}
+
+llvm::Value *CodeGenModule::OpenMPSupportStackTy::getReductionSwitch() {
+	return OpenMPStack.back().ReduceSwitch;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setReductionSwitch(
+	llvm::Value *Switch) {
+	OpenMPStack.back().ReduceSwitch = Switch;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setReductionIPs(
+	llvm::BasicBlock *BB1,
+	llvm::Instruction *IP1,
+	llvm::BasicBlock *BB2,
+	llvm::Instruction *IP2) {
+	OpenMPStack.back().BB1IP = IP1;
+	OpenMPStack.back().BB2IP = IP2;
+	OpenMPStack.back().BB1 = BB1;
+	OpenMPStack.back().BB2 = BB2;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::getReductionIPs(
+	llvm::BasicBlock *&BB1,
+	llvm::Instruction *&IP1,
+	llvm::BasicBlock *&BB2,
+	llvm::Instruction *&IP2) {
+	IP1 = OpenMPStack.back().BB1IP;
+	IP2 = OpenMPStack.back().BB2IP;
+	BB1 = OpenMPStack.back().BB1;
+	BB2 = OpenMPStack.back().BB2;
+}
+
+unsigned
+CodeGenModule::OpenMPSupportStackTy::getNumberOfReductionVars() {
+	return OpenMPStack.back().ReductionTypes.size();
+}
+
+llvm::Value *CodeGenModule::OpenMPSupportStackTy::getReductionLockVar() {
+	return OpenMPStack.back().LockVar;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setReductionLockVar(llvm::Value *Var) {
+	OpenMPStack.back().LockVar = Var;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setNoWait(bool Flag) {
+	OpenMPStack.back().NoWait = Flag;
+}
+
+bool CodeGenModule::OpenMPSupportStackTy::getNoWait() {
+	return OpenMPStack.back().NoWait;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setScheduleChunkSize(
+	int Sched,
+	const Expr *Size) {
+	OpenMPStack.back().Schedule = Sched;
+	OpenMPStack.back().ChunkSize = Size;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::getScheduleChunkSize(
+	int &Sched,
+	const Expr *&Size) {
+	Sched = OpenMPStack.back().Schedule;
+	Size = OpenMPStack.back().ChunkSize;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setMergeable(bool Flag) {
+	OpenMPStack.back().Mergeable = Flag;
+}
+
+bool CodeGenModule::OpenMPSupportStackTy::getMergeable() {
+	return OpenMPStack.back().Mergeable;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setOrdered(bool Flag) {
+	OpenMPStack.back().Ordered = Flag;
+}
+
+bool CodeGenModule::OpenMPSupportStackTy::getOrdered() {
+	return OpenMPStack.back().Ordered;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setHasLastPrivate(bool Flag) {
+	OpenMPStack.back().HasLastPrivate = Flag;
+}
+
+bool CodeGenModule::OpenMPSupportStackTy::hasLastPrivate() {
+	return OpenMPStack.back().HasLastPrivate;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setLastprivateIP(
+	llvm::BasicBlock *BB,
+	llvm::Instruction *IP,
+	llvm::BasicBlock *EndBB) {
+	OpenMPStack.back().LastprivateIP = IP;
+	OpenMPStack.back().LastprivateBB = BB;
+	OpenMPStack.back().LastprivateEndBB = EndBB;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::getLastprivateIP(
+	llvm::BasicBlock *&BB,
+	llvm::Instruction *&IP,
+	llvm::BasicBlock *&EndBB) {
+	IP = OpenMPStack.back().LastprivateIP;
+	BB = OpenMPStack.back().LastprivateBB;
+	EndBB = OpenMPStack.back().LastprivateEndBB;
+}
+
+llvm::Value *CodeGenModule::OpenMPSupportStackTy::getLastIterVar() {
+	return OpenMPStack.back().LastIterVar;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setLastIterVar(llvm::Value *Var) {
+	OpenMPStack.back().LastIterVar = Var;
+}
+
+bool CodeGenModule::OpenMPSupportStackTy::getUntied() {
+	for (OMPStackTy::reverse_iterator I = OpenMPStack.rbegin(),
+		E = OpenMPStack.rend();
+		I != E; ++I) {
+		if (I->NewTask) {
+			return I->Untied;
+		}
+	}
+	return false;
+}
+
+bool CodeGenModule::OpenMPSupportStackTy::getParentUntied() {
+	bool FirstTaskFound = false;
+	for (OMPStackTy::reverse_iterator I = OpenMPStack.rbegin(),
+		E = OpenMPStack.rend();
+		I != E; ++I) {
+		if (FirstTaskFound && I->NewTask) {
+			return I->Untied;
+		}
+		FirstTaskFound = FirstTaskFound || I->NewTask;
+	}
+	return false;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setUntied(bool Flag) {
+	OpenMPStack.back().Untied = Flag;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setTargetDeclare(bool Flag) {
+	OpenMPStack.back().TargetDeclare = Flag;
+}
+bool CodeGenModule::OpenMPSupportStackTy::getTargetDeclare() {
+	for (OMPStackTy::reverse_iterator I = OpenMPStack.rbegin(),
+		E = OpenMPStack.rend();
+		I != E; ++I) {
+		if (I->TargetDeclare) {
+			return true;
+		}
+	}
+	return false;
+}
+void CodeGenModule::OpenMPSupportStackTy::setTarget(bool Flag) {
+	OpenMPStack.back().Target = Flag;
+}
+bool CodeGenModule::OpenMPSupportStackTy::getTarget() {
+	for (OMPStackTy::reverse_iterator I = OpenMPStack.rbegin(),
+		E = OpenMPStack.rend();
+		I != E; ++I) {
+		if (I->Target) {
+			return true;
+		}
+	}
+	return false;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setDistribute(bool Flag) {
+	OpenMPStack.back().Distribute = Flag;
+}
+
+bool CodeGenModule::OpenMPSupportStackTy::getDistribute() {
+	return OpenMPStack.back().Distribute;
+}
+
+
+llvm::Value *CodeGenModule::OpenMPSupportStackTy::getTaskFlags() {
+	return OpenMPStack.back().TaskFlags;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setTaskFlags(llvm::Value *Flags) {
+	OpenMPStack.back().TaskFlags = Flags;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setPTask(llvm::Value *Task, llvm::Value *TaskT, llvm::Type *PTy, QualType PQTy, llvm::Value *PB) {
+	OpenMPStack.back().PTask = Task;
+	OpenMPStack.back().PTaskTValue = TaskT;
+	OpenMPStack.back().TaskPrivateTy = PTy;
+	OpenMPStack.back().TaskPrivateQTy = PQTy;
+	OpenMPStack.back().TaskPrivateBase = PB;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::getPTask(llvm::Value *&Task, llvm::Value *&TaskT, llvm::Type *&PTy, QualType &PQTy, llvm::Value *&PB) {
+	Task = OpenMPStack.back().PTask;
+	TaskT = OpenMPStack.back().PTaskTValue;
+	PTy = OpenMPStack.back().TaskPrivateTy;
+	PQTy = OpenMPStack.back().TaskPrivateQTy;
+	PB = OpenMPStack.back().TaskPrivateBase;
+}
+
+llvm::DenseMap<const ValueDecl *, FieldDecl *> &CodeGenModule::OpenMPSupportStackTy::getTaskFields() {
+	return OpenMPStack.back().TaskFields;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setUntiedData(llvm::Value *UntiedPartIdAddr, llvm::Value *UntiedSwitch,
+	llvm::BasicBlock *UntiedEnd, unsigned UntiedCounter,
+	CodeGenFunction *CGF) {
+	for (OMPStackTy::reverse_iterator I = OpenMPStack.rbegin(),
+		E = OpenMPStack.rend();
+		I != E; ++I) {
+		if (I->NewTask) {
+			I->UntiedPartIdAddr = UntiedPartIdAddr;
+			I->UntiedSwitch = UntiedSwitch;
+			I->UntiedEnd = UntiedEnd;
+			I->UntiedCounter = UntiedCounter;
+			I->ParentCGF = CGF;
+			return;
+		}
+	}
+}
+
+void CodeGenModule::OpenMPSupportStackTy::getUntiedData(llvm::Value *&UntiedPartIdAddr, llvm::Value *&UntiedSwitch,
+	llvm::BasicBlock *&UntiedEnd, unsigned &UntiedCounter) {
+	for (OMPStackTy::reverse_iterator I = OpenMPStack.rbegin(),
+		E = OpenMPStack.rend();
+		I != E; ++I) {
+		if (I->NewTask) {
+			UntiedPartIdAddr = I->UntiedPartIdAddr;
+			UntiedSwitch = I->UntiedSwitch;
+			UntiedEnd = I->UntiedEnd;
+			UntiedCounter = I->UntiedCounter;
+			return;
+		}
+	}
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setParentUntiedData(llvm::Value *UntiedPartIdAddr, llvm::Value *UntiedSwitch,
+	llvm::BasicBlock *UntiedEnd, unsigned UntiedCounter,
+	CodeGenFunction *CGF) {
+	bool FirstTaskFound = false;
+	for (OMPStackTy::reverse_iterator I = OpenMPStack.rbegin(),
+		E = OpenMPStack.rend();
+		I != E; ++I) {
+		if (FirstTaskFound && I->NewTask) {
+			I->UntiedPartIdAddr = UntiedPartIdAddr;
+			I->UntiedSwitch = UntiedSwitch;
+			I->UntiedEnd = UntiedEnd;
+			I->UntiedCounter = UntiedCounter;
+			I->ParentCGF = CGF;
+			return;
+		}
+		FirstTaskFound = FirstTaskFound || I->NewTask;
+	}
+}
+
+void CodeGenModule::OpenMPSupportStackTy::getParentUntiedData(llvm::Value *&UntiedPartIdAddr, llvm::Value *&UntiedSwitch,
+	llvm::BasicBlock *&UntiedEnd, unsigned &UntiedCounter,
+	CodeGenFunction *&CGF) {
+	bool FirstTaskFound = false;
+	for (OMPStackTy::reverse_iterator I = OpenMPStack.rbegin(),
+		E = OpenMPStack.rend();
+		I != E; ++I) {
+		if (FirstTaskFound && I->NewTask) {
+			UntiedPartIdAddr = I->UntiedPartIdAddr;
+			UntiedSwitch = I->UntiedSwitch;
+			UntiedEnd = I->UntiedEnd;
+			UntiedCounter = I->UntiedCounter;
+			CGF = I->ParentCGF;
+			return;
+		}
+		FirstTaskFound = FirstTaskFound || I->NewTask;
+	}
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setNumTeams(Expr *Num) {
+	OpenMPStack.back().NumTeams = Num;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setThreadLimit(Expr *Num) {
+	OpenMPStack.back().ThreadLimit = Num;
+}
+
+Expr *CodeGenModule::OpenMPSupportStackTy::getNumTeams() {
+	return OpenMPStack.back().NumTeams;
+}
+
+Expr *CodeGenModule::OpenMPSupportStackTy::getThreadLimit() {
+	return OpenMPStack.back().ThreadLimit;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::setWaitDepsArgs(llvm::Value **Args) {
+	OpenMPStack.back().WaitDepsArgs = Args;
+}
+
+llvm::Value **CodeGenModule::OpenMPSupportStackTy::getWaitDepsArgs() {
+	return OpenMPStack.back().WaitDepsArgs;
+}
+
+void CodeGenModule::OpenMPSupportStackTy::addOffloadingMap(const Expr* DExpr, llvm::Value *BasePtr, llvm::Value *Ptr, llvm::Value *Size, unsigned Type) {
+	OpenMPStack.back().OffloadingMapDecls.push_back(DExpr);
+	OpenMPStack.back().OffloadingMapBasePtrs.push_back(BasePtr);
+	OpenMPStack.back().OffloadingMapPtrs.push_back(Ptr);
+	OpenMPStack.back().OffloadingMapSizes.push_back(Size);
+	OpenMPStack.back().OffloadingMapTypes.push_back(Type);
+}
+void CodeGenModule::OpenMPSupportStackTy::getOffloadingMapArrays(ArrayRef<const Expr*> &DExprs, ArrayRef<llvm::Value*> &BasePtrs, ArrayRef<llvm::Value*> &Ptrs, ArrayRef<llvm::Value*> &Sizes, ArrayRef<unsigned> &Types) {
+	DExprs = OpenMPStack.back().OffloadingMapDecls;
+	BasePtrs = OpenMPStack.back().OffloadingMapBasePtrs;
+	Ptrs = OpenMPStack.back().OffloadingMapPtrs;
+	Sizes = OpenMPStack.back().OffloadingMapSizes;
+	Types = OpenMPStack.back().OffloadingMapTypes;
+}
+llvm::CallInst*  CodeGenModule::OpenMPSupportStackTy::getOffloadingMapBeginFunctionCall() {
+	return OpenMPStack.back().OffloadingMapBeginFunctionCall;
+}
+void CodeGenModule::OpenMPSupportStackTy::setOffloadingMapBeginFunctionCall(llvm::CallInst *OffloadingMapBeginFunctionCall) {
+	OpenMPStack.back().OffloadingMapBeginFunctionCall = OffloadingMapBeginFunctionCall;
+}
+void CodeGenModule::OpenMPSupportStackTy::setMapsBegin(bool Flag) {
+	OpenMPStack.back().MapsBegin = Flag;
+}
+bool CodeGenModule::OpenMPSupportStackTy::getMapsBegin() {
+	return OpenMPStack.back().MapsBegin;
+}
+void CodeGenModule::OpenMPSupportStackTy::setMapsEnd(bool Flag) {
+	OpenMPStack.back().MapsEnd = Flag;
+}
+bool CodeGenModule::OpenMPSupportStackTy::getMapsEnd() {
+	return OpenMPStack.back().MapsEnd;
+}
+void CodeGenModule::OpenMPSupportStackTy::setOffloadingDevice(llvm::Value *device) {
+	OpenMPStack.back().OffloadingDevice = device;
+}
+llvm::Value *CodeGenModule::OpenMPSupportStackTy::getOffloadingDevice() {
+	return OpenMPStack.back().OffloadingDevice;
+}
+void CodeGenModule::OpenMPSupportStackTy::setOffloadingHostFunctionCall(llvm::CallInst *OffloadingHostFunctionCall) {
+	OpenMPStack.back().OffloadingHostFunctionCall = OffloadingHostFunctionCall;
+}
+llvm::CallInst* CodeGenModule::OpenMPSupportStackTy::getOffloadingHostFunctionCall() {
+	return OpenMPStack.back().OffloadingHostFunctionCall;
+}
+
 llvm::MDTuple *CodeGenModule::CreateVTableBitSetEntry(
     llvm::GlobalVariable *VTable, CharUnits Offset, const CXXRecordDecl *RD) {
   llvm::Metadata *BitsetOps[] = {
Index: lib/CodeGen/CGDecl.cpp
===================================================================
--- lib/CodeGen/CGDecl.cpp
+++ lib/CodeGen/CGDecl.cpp
@@ -21,6 +21,7 @@
 #include "clang/AST/CharUnits.h"
 #include "clang/AST/Decl.h"
 #include "clang/AST/DeclObjC.h"
+#include "clang/AST/DeclOpenMP.h"
 #include "clang/Basic/SourceManager.h"
 #include "clang/Basic/TargetInfo.h"
 #include "clang/CodeGen/CGFunctionInfo.h"
@@ -115,6 +116,9 @@
     return EmitVarDecl(VD);
   }
 
+  case Decl::OMPDeclareTarget:
+	return CGM.EmitOMPDeclareTarget(cast<OMPDeclareTargetDecl>(&D));
+
   case Decl::Typedef:      // typedef int X;
   case Decl::TypeAlias: {  // using X = int; [C++0x]
     const TypedefNameDecl &TD = cast<TypedefNameDecl>(D);
@@ -1861,3 +1865,23 @@
   if (D.hasAttr<AnnotateAttr>())
     EmitVarAnnotations(&D, DeclPtr.getPointer());
 }
+
+void CodeGenModule::EmitOMPDeclareTarget(const OMPDeclareTargetDecl *D) {
+
+	// Create a region for the declare target so the the codegen knows
+	// that is a valid region for a target
+	OpenMPSupport.startOpenMPRegion(false);
+	OpenMPSupport.setTargetDeclare(true);
+
+	for (DeclContext::decl_iterator I = D->decls_begin(), E = D->decls_end();
+	I != E; ++I) {
+		if (const VarDecl *VD = dyn_cast<VarDecl>(*I))
+			if (VD->getTemplateSpecializationKind() != TSK_ExplicitSpecialization &&
+				VD->getTemplateSpecializationKind() != TSK_Undeclared)
+				continue;
+
+		EmitTopLevelDecl(*I);
+	}
+
+	OpenMPSupport.endOpenMPRegion();
+}
\ No newline at end of file
Index: lib/Basic/OpenMPKinds.cpp
===================================================================
--- lib/Basic/OpenMPKinds.cpp
+++ lib/Basic/OpenMPKinds.cpp
@@ -432,6 +432,9 @@
       break;
     }
     break;
+	// No clauses allowed for 'omp [end] declare target' constructs.
+  case OMPD_declare_target:
+  case OMPD_end_declare_target:
   case OMPD_unknown:
   case OMPD_threadprivate:
   case OMPD_section:
Index: lib/AST/MicrosoftMangle.cpp
===================================================================
--- lib/AST/MicrosoftMangle.cpp
+++ lib/AST/MicrosoftMangle.cpp
@@ -19,6 +19,7 @@
 #include "clang/AST/Decl.h"
 #include "clang/AST/DeclCXX.h"
 #include "clang/AST/DeclObjC.h"
+#include "clang/AST/DeclOpenMP.h"
 #include "clang/AST/DeclTemplate.h"
 #include "clang/AST/Expr.h"
 #include "clang/AST/ExprCXX.h"
@@ -361,10 +362,10 @@
     const DeclContext *DC = getEffectiveDeclContext(D);
     // Check for extern variable declared locally.
     if (DC->isFunctionOrMethod() && D->hasLinkage())
-      while (!DC->isNamespace() && !DC->isTranslationUnit())
+      while (!DC->isNamespace() && !DC->isTranslationUnitOrDeclareTarget())
         DC = getEffectiveParentContext(DC);
 
-    if (DC->isTranslationUnit() && D->getFormalLinkage() == InternalLinkage &&
+    if (DC->isTranslationUnitOrDeclareTarget() && D->getFormalLinkage() == InternalLinkage &&
         !isa<VarTemplateSpecializationDecl>(D) &&
         D->getIdentifier() != nullptr)
       return false;
@@ -864,7 +865,7 @@
   //           ::= <substitution> [<postfix>]
   const DeclContext *DC = getEffectiveDeclContext(ND);
 
-  while (!DC->isTranslationUnit()) {
+  while (!DC->isTranslationUnitOrDeclareTarget()) {
     if (isa<TagDecl>(ND) || isa<VarDecl>(ND)) {
       unsigned Disc;
       if (Context.getNextDiscriminator(ND, Disc)) {
Index: lib/AST/ItaniumMangle.cpp
===================================================================
--- lib/AST/ItaniumMangle.cpp
+++ lib/AST/ItaniumMangle.cpp
@@ -20,6 +20,7 @@
 #include "clang/AST/Decl.h"
 #include "clang/AST/DeclCXX.h"
 #include "clang/AST/DeclObjC.h"
+#include "clang/AST/DeclOpenMP.h"
 #include "clang/AST/DeclTemplate.h"
 #include "clang/AST/Expr.h"
 #include "clang/AST/ExprCXX.h"
@@ -90,7 +91,7 @@
 
 static const RecordDecl *GetLocalClassDecl(const Decl *D) {
   const DeclContext *DC = getEffectiveDeclContext(D);
-  while (!DC->isNamespace() && !DC->isTranslationUnit()) {
+  while (!DC->isNamespace() && !DC->isTranslationUnitOrDeclareTarget()) {
     if (isLocalContainerContext(DC))
       return dyn_cast<RecordDecl>(D);
     D = cast<Decl>(DC);
@@ -444,9 +445,9 @@
     const DeclContext *DC = getEffectiveDeclContext(D);
     // Check for extern variable declared locally.
     if (DC->isFunctionOrMethod() && D->hasLinkage())
-      while (!DC->isNamespace() && !DC->isTranslationUnit())
+      while (!DC->isNamespace() && !DC->isTranslationUnitOrDeclareTarget())
         DC = getEffectiveParentContext(DC);
-    if (DC->isTranslationUnit() && D->getFormalLinkage() != InternalLinkage &&
+    if (DC->isTranslationUnitOrDeclareTarget() && D->getFormalLinkage() != InternalLinkage &&
         !isa<VarTemplateSpecializationDecl>(D))
       return false;
   }
@@ -537,7 +538,7 @@
 /// Return whether a given namespace is the 'std' namespace.
 static bool isStd(const NamespaceDecl *NS) {
   if (!IgnoreLinkageSpecDecls(getEffectiveParentContext(NS))
-                                ->isTranslationUnit())
+                                ->isTranslationUnitOrDeclareTarget())
     return false;
   
   const IdentifierInfo *II = NS->getOriginalNamespace()->getIdentifier();
@@ -593,7 +594,7 @@
   // FIXME: This is a hack; extern variables declared locally should have
   // a proper semantic declaration context!
   if (isLocalContainerContext(DC) && ND->hasLinkage() && !isLambda(ND))
-    while (!DC->isNamespace() && !DC->isTranslationUnit())
+    while (!DC->isNamespace() && !DC->isTranslationUnitOrDeclareTarget())
       DC = getEffectiveParentContext(DC);
   else if (GetLocalClassDecl(ND)) {
     mangleLocalName(ND);
@@ -602,7 +603,7 @@
 
   DC = IgnoreLinkageSpecDecls(DC);
 
-  if (DC->isTranslationUnit() || isStdNamespace(DC)) {
+  if (DC->isTranslationUnitOrDeclareTarget() || isStdNamespace(DC)) {
     // Check if we have a template.
     const TemplateArgumentList *TemplateArgs = nullptr;
     if (const TemplateDecl *TD = isTemplate(ND, TemplateArgs)) {
@@ -627,7 +628,7 @@
                                 unsigned NumTemplateArgs) {
   const DeclContext *DC = IgnoreLinkageSpecDecls(getEffectiveDeclContext(TD));
 
-  if (DC->isTranslationUnit() || isStdNamespace(DC)) {
+  if (DC->isTranslationUnitOrDeclareTarget() || isStdNamespace(DC)) {
     mangleUnscopedTemplateName(TD);
     mangleTemplateArgs(TemplateArgs, NumTemplateArgs);
   } else {
@@ -1342,7 +1343,7 @@
 
   DC = IgnoreLinkageSpecDecls(DC);
 
-  if (DC->isTranslationUnit())
+  if (DC->isTranslationUnitOrDeclareTarget())
     return;
 
   if (NoFunction && isLocalContainerContext(DC))
Index: lib/AST/DeclPrinter.cpp
===================================================================
--- lib/AST/DeclPrinter.cpp
+++ lib/AST/DeclPrinter.cpp
@@ -92,6 +92,7 @@
     void VisitUsingDecl(UsingDecl *D);
     void VisitUsingShadowDecl(UsingShadowDecl *D);
     void VisitOMPThreadPrivateDecl(OMPThreadPrivateDecl *D);
+	void VisitOMPDeclareTargetDecl(OMPDeclareTargetDecl *D);
 
     void PrintTemplateParameters(const TemplateParameterList *Params,
                                  const TemplateArgumentList *Args = nullptr);
@@ -333,7 +334,7 @@
 
     // FIXME: Need to be able to tell the DeclPrinter when
     const char *Terminator = nullptr;
-    if (isa<OMPThreadPrivateDecl>(*D))
+    if (isa<OMPThreadPrivateDecl>(*D) || isa<OMPDeclareTargetDecl>(*D))
       Terminator = nullptr;
     else if (isa<FunctionDecl>(*D) &&
              cast<FunctionDecl>(*D)->isThisDeclarationADefinition())
@@ -1307,6 +1308,12 @@
     Out << ';';
 }
 
+void DeclPrinter::VisitOMPDeclareTargetDecl(OMPDeclareTargetDecl *D) {
+	Out << "#pragma omp declare target\n";
+	VisitDeclContext(D);
+	Out << "#pragma omp end declare target\n";
+}
+
 void DeclPrinter::VisitObjCPropertyImplDecl(ObjCPropertyImplDecl *PID) {
   if (PID->getPropertyImplementation() == ObjCPropertyImplDecl::Synthesize)
     Out << "@synthesize ";
Index: lib/AST/DeclOpenMP.cpp
===================================================================
--- lib/AST/DeclOpenMP.cpp
+++ lib/AST/DeclOpenMP.cpp
@@ -7,7 +7,7 @@
 //
 //===----------------------------------------------------------------------===//
 /// \file
-/// \brief This file implements OMPThreadPrivateDecl class.
+/// \brief This file implements OMPThreadPrivateDecl. OMPDeclareTarget class.
 ///
 //===----------------------------------------------------------------------===//
 
@@ -52,3 +52,24 @@
   std::copy(VL.begin(), VL.end(), Vars);
 }
 
+
+//===----------------------------------------------------------------------===//
+// OMPDeclareTargetDecl Implementation.
+//===----------------------------------------------------------------------===//
+
+void OMPDeclareTargetDecl::anchor() {}
+
+OMPDeclareTargetDecl *
+OMPDeclareTargetDecl::Create(ASTContext &C, DeclContext *DC, SourceLocation L) {
+	OMPDeclareTargetDecl *D =
+		new (C, DC) OMPDeclareTargetDecl(OMPDeclareTarget, DC, L);
+	return D;
+}
+
+OMPDeclareTargetDecl *OMPDeclareTargetDecl::CreateDeserialized(ASTContext &C,
+	unsigned ID) {
+	// Realign
+	OMPDeclareTargetDecl *D =
+		new (C, ID) OMPDeclareTargetDecl(OMPDeclareTarget, 0, SourceLocation());
+	return D;
+}
\ No newline at end of file
Index: lib/AST/DeclBase.cpp
===================================================================
--- lib/AST/DeclBase.cpp
+++ lib/AST/DeclBase.cpp
@@ -198,7 +198,7 @@
 
 const DeclContext *Decl::getParentFunctionOrMethod() const {
   for (const DeclContext *DC = getDeclContext();
-       DC && !DC->isTranslationUnit() && !DC->isNamespace(); 
+       DC && !DC->isTranslationUnitOrDeclareTarget() && !DC->isNamespace();
        DC = DC->getParent())
     if (DC->isFunctionOrMethod())
       return DC;
@@ -650,6 +650,7 @@
     case ObjCCategoryImpl:
     case Import:
     case OMPThreadPrivate:
+	case OMPDeclareTarget:
     case Empty:
       // Never looked up by name.
       return 0;
@@ -869,7 +870,7 @@
     return ND->getParent()->isStdNamespace();
   }
 
-  if (!getParent()->getRedeclContext()->isTranslationUnit())
+  if (!getParent()->getRedeclContext()->isTranslationUnitOrDeclareTarget())
     return false;
 
   const IdentifierInfo *II = ND->getIdentifier();
@@ -913,6 +914,8 @@
     return !cast<EnumDecl>(this)->isScoped();
   else if (DeclKind == Decl::LinkageSpec)
     return true;
+  else if (DeclKind == Decl::OMPDeclareTarget)
+	  return true;
 
   return false;
 }
@@ -952,6 +955,7 @@
   case Decl::LinkageSpec:
   case Decl::Block:
   case Decl::Captured:
+  case Decl::OMPDeclareTarget:
     // There is only one DeclContext for these entities.
     return this;
 
Index: lib/AST/Decl.cpp
===================================================================
--- lib/AST/Decl.cpp
+++ lib/AST/Decl.cpp
@@ -18,6 +18,7 @@
 #include "clang/AST/Attr.h"
 #include "clang/AST/DeclCXX.h"
 #include "clang/AST/DeclObjC.h"
+#include "clang/AST/DeclOpenMP.h"
 #include "clang/AST/DeclTemplate.h"
 #include "clang/AST/Expr.h"
 #include "clang/AST/ExprCXX.h"
@@ -2481,7 +2482,7 @@
          getDeclName().getCXXOverloadedOperator() == OO_Array_New ||
          getDeclName().getCXXOverloadedOperator() == OO_Array_Delete);
 
-  if (!getDeclContext()->getRedeclContext()->isTranslationUnit())
+  if (!getDeclContext()->getRedeclContext()->isTranslationUnitOrDeclareTarget())
     return false;
 
   const auto *proto = getType()->castAs<FunctionProtoType>();
@@ -2510,7 +2511,7 @@
     return false;
 
   // This can only fail for an invalid 'operator new' declaration.
-  if (!getDeclContext()->getRedeclContext()->isTranslationUnit())
+  if (!getDeclContext()->getRedeclContext()->isTranslationUnitOrDeclareTarget())
     return false;
 
   const auto *FPT = getType()->castAs<FunctionProtoType>();
@@ -2745,7 +2746,7 @@
 
 static bool RedeclForcesDefC99(const FunctionDecl *Redecl) {
   // Only consider file-scope declarations in this test.
-  if (!Redecl->getLexicalDeclContext()->isTranslationUnit())
+  if (!Redecl->getLexicalDeclContext()->isTranslationUnitOrDeclareTarget())
     return false;
 
   // Only consider explicit declarations; the presence of a builtin for a
Index: lib/AST/ASTContext.cpp
===================================================================
--- lib/AST/ASTContext.cpp
+++ lib/AST/ASTContext.cpp
@@ -8400,7 +8400,7 @@
     // We never need to emit an uninstantiated function template.
     if (FD->getTemplatedKind() == FunctionDecl::TK_FunctionTemplate)
       return false;
-  } else if (isa<OMPThreadPrivateDecl>(D))
+  } else if (isa<OMPThreadPrivateDecl>(D) || isa<OMPDeclareTargetDecl>(D))
     return true;
   else
     return false;
Index: include/clang/Serialization/ASTBitCodes.h
===================================================================
--- include/clang/Serialization/ASTBitCodes.h
+++ include/clang/Serialization/ASTBitCodes.h
@@ -1152,6 +1152,8 @@
       DECL_EMPTY,
       /// \brief An ObjCTypeParamDecl record.
       DECL_OBJC_TYPE_PARAM,
+      /// \brief An OMPDeclareTargetDecl record.
+      DECL_OMP_DECLARETARGET,
     };
 
     /// \brief Record codes for each kind of statement or expression.
Index: include/clang/Sema/Sema.h
===================================================================
--- include/clang/Sema/Sema.h
+++ include/clang/Sema/Sema.h
@@ -145,6 +145,7 @@
   class ObjCProtocolDecl;
   class OMPThreadPrivateDecl;
   class OMPClause;
+  class OMPDeclareTargetDecl;
   struct OverloadCandidate;
   class OverloadCandidateSet;
   class OverloadExpr;
@@ -7815,6 +7816,13 @@
                                      SourceLocation Loc,
                                      ArrayRef<Expr *> VarList);
 
+  bool ActOnStartOpenMPDeclareTargetDirective(Scope *S, SourceLocation Loc);
+  void ActOnOpenMPDeclareTargetDecls(DeclGroupPtrTy Decls);
+  DeclGroupPtrTy ActOnFinishOpenMPDeclareTargetDirective();
+  void ActOnOpenMPDeclareTargetDirectiveError();
+  void CheckDeclIsAllowedInOpenMPTarget(Expr *E, Decl *D);
+  bool IsDeclContextInOpenMPTarget(DeclContext *DC);
+
   /// \brief Initialization of captured region for OpenMP region.
   void ActOnOpenMPRegionStart(OpenMPDirectiveKind DKind, Scope *CurScope);
   /// \brief End of OpenMP region.
Index: include/clang/Parse/Parser.h
===================================================================
--- include/clang/Parse/Parser.h
+++ include/clang/Parse/Parser.h
@@ -2426,7 +2426,7 @@
   //===--------------------------------------------------------------------===//
   // OpenMP: Directives and clauses.
   /// \brief Parses declarative OpenMP directives.
-  DeclGroupPtrTy ParseOpenMPDeclarativeDirective();
+  DeclGroupPtrTy ParseOpenMPDeclarativeDirective(AccessSpecifier AS);
   /// \brief Parses simple list of variables.
   ///
   /// \param Kind Kind of the directive.
Index: include/clang/Basic/OpenMPKinds.h
===================================================================
--- include/clang/Basic/OpenMPKinds.h
+++ include/clang/Basic/OpenMPKinds.h
@@ -26,7 +26,8 @@
 #define OPENMP_DIRECTIVE_EXT(Name, Str) \
   OMPD_##Name,
 #include "clang/Basic/OpenMPKinds.def"
-  OMPD_unknown
+  OMPD_unknown,
+  OMPD_empty
 };
 
 /// \brief OpenMP clauses.
Index: include/clang/Basic/OpenMPKinds.def
===================================================================
--- include/clang/Basic/OpenMPKinds.def
+++ include/clang/Basic/OpenMPKinds.def
@@ -123,6 +123,8 @@
 OPENMP_DIRECTIVE_EXT(cancellation_point, "cancellation point")
 OPENMP_DIRECTIVE(taskloop)
 OPENMP_DIRECTIVE_EXT(taskloop_simd, "taskloop simd")
+OPENMP_DIRECTIVE_EXT(declare_target, "declare target")
+OPENMP_DIRECTIVE_EXT(end_declare_target, "end declare target")
 
 // OpenMP clauses.
 OPENMP_CLAUSE(if, OMPIfClause)
Index: include/clang/Basic/DiagnosticSemaKinds.td
===================================================================
--- include/clang/Basic/DiagnosticSemaKinds.td
+++ include/clang/Basic/DiagnosticSemaKinds.td
@@ -7659,6 +7659,8 @@
   "arguments of '#pragma omp %0' must have %select{global storage|static storage duration}1">;
 def err_omp_ref_type_arg : Error<
   "arguments of '#pragma omp %0' cannot be of reference type %1">;
+def err_omp_region_not_file_context : Error<
+  "directive must be at file or namespace scope">;
 def err_omp_var_scope : Error<
   "'#pragma omp %0' must appear in the scope of the %q1 variable declaration">;
 def err_omp_var_used : Error<
@@ -7716,6 +7718,8 @@
 def err_omp_not_integral : Error<
   "expression must have integral or unscoped enumeration "
   "type, not %0">;
+def err_omp_threadprivate_in_target : Error<
+  "threadprivate variables cannot be used in target constructs">;
 def err_omp_incomplete_type : Error<
   "expression has incomplete class type %0">;
 def err_omp_explicit_conversion : Error<
@@ -7742,6 +7746,9 @@
 def warn_omp_alignment_not_power_of_two : Warning<
   "aligned clause will be ignored because the requested alignment is not a power of 2">,
   InGroup<OpenMPClauses>;
+def warn_omp_not_in_target_context : Warning<
+  "declaration is not declared in any declare target region">,
+  InGroup<OpenMPClauses>;
 def err_omp_aligned_expected_array_or_ptr : Error<
   "argument of aligned clause should be array"
   "%select{ or pointer|, pointer, reference to array or reference to pointer}1"
Index: include/clang/Basic/DiagnosticParseKinds.td
===================================================================
--- include/clang/Basic/DiagnosticParseKinds.td
+++ include/clang/Basic/DiagnosticParseKinds.td
@@ -928,6 +928,8 @@
   "'#pragma omp %0' cannot be an immediate substatement">;
 def err_omp_expected_identifier_for_critical : Error<
   "expected identifier specifying the name of the 'omp critical' directive">;
+def err_expected_end_declare_target : Error<
+  "expected '#pragma omp end declare target'">;
 def err_omp_unknown_map_type : Error<
   "incorrect map type, expected one of 'to', 'from', 'tofrom', 'alloc', 'release', or 'delete'">;
 def err_omp_unknown_map_type_modifier : Error<
Index: include/clang/Basic/DeclNodes.td
===================================================================
--- include/clang/Basic/DeclNodes.td
+++ include/clang/Basic/DeclNodes.td
@@ -84,5 +84,6 @@
 def ClassScopeFunctionSpecialization : Decl;
 def Import : Decl;
 def OMPThreadPrivate : Decl;
+def OMPDeclareTarget : Decl, DeclContext;
 def Empty : Decl;
 
Index: include/clang/AST/RecursiveASTVisitor.h
===================================================================
--- include/clang/AST/RecursiveASTVisitor.h
+++ include/clang/AST/RecursiveASTVisitor.h
@@ -1425,6 +1425,8 @@
   }
 })
 
+DEF_TRAVERSE_DECL(OMPDeclareTargetDecl, {})
+
 // A helper method for TemplateDecl's children.
 template <typename Derived>
 bool RecursiveASTVisitor<Derived>::TraverseTemplateParameterListHelper(
Index: include/clang/AST/DeclOpenMP.h
===================================================================
--- include/clang/AST/DeclOpenMP.h
+++ include/clang/AST/DeclOpenMP.h
@@ -15,7 +15,9 @@
 #ifndef LLVM_CLANG_AST_DECLOPENMP_H
 #define LLVM_CLANG_AST_DECLOPENMP_H
 
-#include "clang/AST/DeclBase.h"
+#include "clang/AST/Decl.h"
+#include "clang/AST/Expr.h"
+#include "clang/AST/Type.h"
 #include "llvm/ADT/ArrayRef.h"
 
 namespace clang {
@@ -85,6 +87,39 @@
   static bool classofKind(Kind K) { return K == OMPThreadPrivate; }
 };
 
+/// For example, in the following, declared target variable 'foo':
+///
+/// \code
+/// #pragma omp declare target
+/// int foo;
+/// #pragma omp end declare target
+/// \endcode
+///
+class OMPDeclareTargetDecl : public Decl, public DeclContext {
+	friend class ASTDeclReader;
+
+	virtual void anchor();
+
+	OMPDeclareTargetDecl(Kind DK, DeclContext *DC, SourceLocation L)
+		: Decl(DK, DC, L), DeclContext(DK) {
+		setModulePrivate();
+	}
+
+public:
+	static OMPDeclareTargetDecl *Create(ASTContext &C, DeclContext *DC,
+		SourceLocation L);
+	static OMPDeclareTargetDecl *CreateDeserialized(ASTContext &C, unsigned ID);
+
+	static bool classof(const Decl *D) { return classofKind(D->getKind()); }
+	static bool classofKind(Kind K) { return K == OMPDeclareTarget; }
+	static DeclContext *castToDeclContext(const OMPDeclareTargetDecl *D) {
+		return static_cast<DeclContext *>(const_cast<OMPDeclareTargetDecl *>(D));
+	}
+	static OMPDeclareTargetDecl *castFromDeclContext(const DeclContext *DC) {
+		return static_cast<OMPDeclareTargetDecl *>(const_cast<DeclContext *>(DC));
+	}
+};
+
 }  // end namespace clang
 
 #endif
Index: include/clang/AST/DeclBase.h
===================================================================
--- include/clang/AST/DeclBase.h
+++ include/clang/AST/DeclBase.h
@@ -161,7 +161,7 @@
     /// This declaration is a function-local extern declaration of a
     /// variable or function. This may also be IDNS_Ordinary if it
     /// has been declared outside any function.
-    IDNS_LocalExtern         = 0x0800
+    IDNS_LocalExtern         = 0x0800,
   };
 
   /// ObjCDeclQualifier - 'Qualifiers' written next to the return and
@@ -1265,6 +1265,12 @@
     return DeclKind == Decl::TranslationUnit;
   }
 
+  bool isOMPDeclareTarget() const { return DeclKind == Decl::OMPDeclareTarget; }
+
+  bool isTranslationUnitOrDeclareTarget() const {
+	  return isOMPDeclareTarget() || isTranslationUnit();
+  }
+
   bool isRecord() const {
     return DeclKind >= Decl::firstRecord && DeclKind <= Decl::lastRecord;
   }
_______________________________________________
cfe-commits mailing list
cfe-commits@lists.llvm.org
http://lists.llvm.org/cgi-bin/mailman/listinfo/cfe-commits

Reply via email to