[flang-commits] [flang] [llvm] [Flang][OpenMP] Initial defaultmap implementation (PR #135226)

via flang-commits flang-commits at lists.llvm.org
Thu May 1 17:44:36 PDT 2025


https://github.com/agozillon updated https://github.com/llvm/llvm-project/pull/135226

>From bcdabc07bfb091785191ba7bf98a24d2f844d1f6 Mon Sep 17 00:00:00 2001
From: agozillon <Andrew.Gozillon at amd.com>
Date: Thu, 1 May 2025 19:43:27 -0500
Subject: [PATCH] [Flang][OpenMP] Initial defaultmap implementation

This aims to implement most of the initial arguments for defaultmap aside from firstprivate and none, and some of the more recent OpenMP 6 additions which will come in subsequent updates.
---
 flang/include/flang/Parser/parse-tree.h       |   4 +-
 flang/lib/Lower/OpenMP/ClauseProcessor.cpp    |  20 ++
 flang/lib/Lower/OpenMP/ClauseProcessor.h      |   6 +
 flang/lib/Lower/OpenMP/Clauses.cpp            |   2 +-
 flang/lib/Lower/OpenMP/OpenMP.cpp             | 218 +++++++++++++-----
 flang/lib/Parser/openmp-parsers.cpp           |   5 +-
 .../Todo/defaultmap-clause-firstprivate.f90   |  11 +
 .../OpenMP/Todo/defaultmap-clause-none.f90    |  11 +
 .../Lower/OpenMP/Todo/defaultmap-clause.f90   |   8 -
 flang/test/Lower/OpenMP/defaultmap.f90        | 105 +++++++++
 .../test/Parser/OpenMP/defaultmap-clause.f90  |  16 ++
 .../fortran/target-defaultmap-present.f90     |  34 +++
 .../offloading/fortran/target-defaultmap.f90  | 166 +++++++++++++
 13 files changed, 533 insertions(+), 73 deletions(-)
 create mode 100644 flang/test/Lower/OpenMP/Todo/defaultmap-clause-firstprivate.f90
 create mode 100644 flang/test/Lower/OpenMP/Todo/defaultmap-clause-none.f90
 delete mode 100644 flang/test/Lower/OpenMP/Todo/defaultmap-clause.f90
 create mode 100644 flang/test/Lower/OpenMP/defaultmap.f90
 create mode 100644 offload/test/offloading/fortran/target-defaultmap-present.f90
 create mode 100644 offload/test/offloading/fortran/target-defaultmap.f90

diff --git a/flang/include/flang/Parser/parse-tree.h b/flang/include/flang/Parser/parse-tree.h
index e39ecc13f4eec..2720c67399092 100644
--- a/flang/include/flang/Parser/parse-tree.h
+++ b/flang/include/flang/Parser/parse-tree.h
@@ -4133,8 +4133,8 @@ struct OmpDefaultClause {
 //    PRESENT                                       // since 5.1
 struct OmpDefaultmapClause {
   TUPLE_CLASS_BOILERPLATE(OmpDefaultmapClause);
-  ENUM_CLASS(
-      ImplicitBehavior, Alloc, To, From, Tofrom, Firstprivate, None, Default)
+  ENUM_CLASS(ImplicitBehavior, Alloc, To, From, Tofrom, Firstprivate, None,
+      Default, Present)
   MODIFIER_BOILERPLATE(OmpVariableCategory);
   std::tuple<ImplicitBehavior, MODIFIERS()> t;
 };
diff --git a/flang/lib/Lower/OpenMP/ClauseProcessor.cpp b/flang/lib/Lower/OpenMP/ClauseProcessor.cpp
index 77b4622547d7a..98ca5d21d3ad8 100644
--- a/flang/lib/Lower/OpenMP/ClauseProcessor.cpp
+++ b/flang/lib/Lower/OpenMP/ClauseProcessor.cpp
@@ -856,6 +856,26 @@ static bool isVectorSubscript(const evaluate::Expr<T> &expr) {
   return false;
 }
 
+bool ClauseProcessor::processDefaultMap(lower::StatementContext &stmtCtx,
+                                        DefaultMapsTy &result) const {
+  auto process = [&](const omp::clause::Defaultmap &clause,
+                     const parser::CharBlock &) {
+    using Defmap = omp::clause::Defaultmap;
+    clause::Defaultmap::VariableCategory variableCategory =
+        Defmap::VariableCategory::All;
+    // Variable Category is optional, if not specified defaults to all.
+    // Multiples of the same category are illegal as are any other
+    // defaultmaps being specified when a user specified all is in place,
+    // however, this should be handled earlier during semantics.
+    if (auto varCat =
+            std::get<std::optional<Defmap::VariableCategory>>(clause.t))
+      variableCategory = varCat.value_or(Defmap::VariableCategory::All);
+    auto behaviour = std::get<Defmap::ImplicitBehavior>(clause.t);
+    result[variableCategory] = behaviour;
+  };
+  return findRepeatableClause<omp::clause::Defaultmap>(process);
+}
+
 bool ClauseProcessor::processDepend(lower::SymMap &symMap,
                                     lower::StatementContext &stmtCtx,
                                     mlir::omp::DependClauseOps &result) const {
diff --git a/flang/lib/Lower/OpenMP/ClauseProcessor.h b/flang/lib/Lower/OpenMP/ClauseProcessor.h
index bdddeb145b496..2d3d2946838d7 100644
--- a/flang/lib/Lower/OpenMP/ClauseProcessor.h
+++ b/flang/lib/Lower/OpenMP/ClauseProcessor.h
@@ -32,6 +32,10 @@ namespace Fortran {
 namespace lower {
 namespace omp {
 
+// Container type for tracking user specified Defaultmaps for a target region
+using DefaultMapsTy = std::map<clause::Defaultmap::VariableCategory,
+                               clause::Defaultmap::ImplicitBehavior>;
+
 /// Class that handles the processing of OpenMP clauses.
 ///
 /// Its `process<ClauseName>()` methods perform MLIR code generation for their
@@ -106,6 +110,8 @@ class ClauseProcessor {
   bool processCopyin() const;
   bool processCopyprivate(mlir::Location currentLocation,
                           mlir::omp::CopyprivateClauseOps &result) const;
+  bool processDefaultMap(lower::StatementContext &stmtCtx,
+                         DefaultMapsTy &result) const;
   bool processDepend(lower::SymMap &symMap, lower::StatementContext &stmtCtx,
                      mlir::omp::DependClauseOps &result) const;
   bool
diff --git a/flang/lib/Lower/OpenMP/Clauses.cpp b/flang/lib/Lower/OpenMP/Clauses.cpp
index c258bef2e4427..f3088b18b77ff 100644
--- a/flang/lib/Lower/OpenMP/Clauses.cpp
+++ b/flang/lib/Lower/OpenMP/Clauses.cpp
@@ -612,7 +612,7 @@ Defaultmap make(const parser::OmpClause::Defaultmap &inp,
       MS(Firstprivate, Firstprivate)
       MS(None,         None)
       MS(Default,      Default)
-      // MS(, Present)  missing-in-parser
+      MS(Present,      Present)
       // clang-format on
   );
 
diff --git a/flang/lib/Lower/OpenMP/OpenMP.cpp b/flang/lib/Lower/OpenMP/OpenMP.cpp
index 47e7c266ff7d3..2ecbbc526378f 100644
--- a/flang/lib/Lower/OpenMP/OpenMP.cpp
+++ b/flang/lib/Lower/OpenMP/OpenMP.cpp
@@ -1700,11 +1700,13 @@ static void genTargetClauses(
     lower::SymMap &symTable, lower::StatementContext &stmtCtx,
     lower::pft::Evaluation &eval, const List<Clause> &clauses,
     mlir::Location loc, mlir::omp::TargetOperands &clauseOps,
+    DefaultMapsTy &defaultMaps,
     llvm::SmallVectorImpl<const semantics::Symbol *> &hasDeviceAddrSyms,
     llvm::SmallVectorImpl<const semantics::Symbol *> &isDevicePtrSyms,
     llvm::SmallVectorImpl<const semantics::Symbol *> &mapSyms) {
   ClauseProcessor cp(converter, semaCtx, clauses);
   cp.processBare(clauseOps);
+  cp.processDefaultMap(stmtCtx, defaultMaps);
   cp.processDepend(symTable, stmtCtx, clauseOps);
   cp.processDevice(stmtCtx, clauseOps);
   cp.processHasDeviceAddr(stmtCtx, clauseOps, hasDeviceAddrSyms);
@@ -1719,9 +1721,8 @@ static void genTargetClauses(
   cp.processNowait(clauseOps);
   cp.processThreadLimit(stmtCtx, clauseOps);
 
-  cp.processTODO<clause::Allocate, clause::Defaultmap, clause::InReduction,
-                 clause::UsesAllocators>(loc,
-                                         llvm::omp::Directive::OMPD_target);
+  cp.processTODO<clause::Allocate, clause::InReduction, clause::UsesAllocators>(
+      loc, llvm::omp::Directive::OMPD_target);
 
   // `target private(..)` is only supported in delayed privatization mode.
   if (!enableDelayedPrivatizationStaging)
@@ -2231,6 +2232,146 @@ genSingleOp(lower::AbstractConverter &converter, lower::SymMap &symTable,
       queue, item, clauseOps);
 }
 
+static clause::Defaultmap::ImplicitBehavior
+getDefaultmapIfPresent(DefaultMapsTy &defaultMaps, mlir::Type varType) {
+  using DefMap = clause::Defaultmap;
+
+  if (defaultMaps.empty())
+    return DefMap::ImplicitBehavior::Default;
+
+  if (llvm::is_contained(defaultMaps, DefMap::VariableCategory::All))
+    return defaultMaps[DefMap::VariableCategory::All];
+
+  // NOTE: Unsure if complex and/or vector falls into a scalar type
+  // or aggregate, but the current default implicit behaviour is to
+  // treat them as such (c_ptr has its own behaviour, so perhaps
+  // being lumped in as a scalar isn't the right thing).
+  if ((fir::isa_trivial(varType) || fir::isa_char(varType) ||
+       fir::isa_builtin_cptr_type(varType)) &&
+      llvm::is_contained(defaultMaps, DefMap::VariableCategory::Scalar))
+    return defaultMaps[DefMap::VariableCategory::Scalar];
+
+  if (fir::isPointerType(varType) &&
+      llvm::is_contained(defaultMaps, DefMap::VariableCategory::Pointer))
+    return defaultMaps[DefMap::VariableCategory::Pointer];
+
+  if (fir::isAllocatableType(varType) &&
+      llvm::is_contained(defaultMaps, DefMap::VariableCategory::Allocatable))
+    return defaultMaps[DefMap::VariableCategory::Allocatable];
+
+  if (fir::isa_aggregate(varType) &&
+      llvm::is_contained(defaultMaps, DefMap::VariableCategory::Aggregate)) {
+    return defaultMaps[DefMap::VariableCategory::Aggregate];
+  }
+
+  return DefMap::ImplicitBehavior::Default;
+}
+
+static std::pair<llvm::omp::OpenMPOffloadMappingFlags,
+                 mlir::omp::VariableCaptureKind>
+getImplicitMapTypeAndKind(fir::FirOpBuilder &firOpBuilder,
+                          lower::AbstractConverter &converter,
+                          DefaultMapsTy &defaultMaps, mlir::Type varType,
+                          mlir::Location loc, const semantics::Symbol &sym) {
+  using DefMap = clause::Defaultmap;
+  // Check if a value of type `type` can be passed to the kernel by value.
+  // All kernel parameters are of pointer type, so if the value can be
+  // represented inside of a pointer, then it can be passed by value.
+  auto isLiteralType = [&](mlir::Type type) {
+    const mlir::DataLayout &dl = firOpBuilder.getDataLayout();
+    mlir::Type ptrTy =
+        mlir::LLVM::LLVMPointerType::get(&converter.getMLIRContext());
+    uint64_t ptrSize = dl.getTypeSize(ptrTy);
+    uint64_t ptrAlign = dl.getTypePreferredAlignment(ptrTy);
+
+    auto [size, align] = fir::getTypeSizeAndAlignmentOrCrash(
+        loc, type, dl, converter.getKindMap());
+    return size <= ptrSize && align <= ptrAlign;
+  };
+
+  llvm::omp::OpenMPOffloadMappingFlags mapFlag =
+      llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_IMPLICIT;
+
+  auto implicitBehaviour = getDefaultmapIfPresent(defaultMaps, varType);
+  if (implicitBehaviour == DefMap::ImplicitBehavior::Default) {
+    mlir::omp::VariableCaptureKind captureKind =
+        mlir::omp::VariableCaptureKind::ByRef;
+
+    // If a variable is specified in declare target link and if device
+    // type is not specified as `nohost`, it needs to be mapped tofrom
+    mlir::ModuleOp mod = firOpBuilder.getModule();
+    mlir::Operation *op = mod.lookupSymbol(converter.mangleName(sym));
+    auto declareTargetOp =
+        llvm::dyn_cast_if_present<mlir::omp::DeclareTargetInterface>(op);
+    if (declareTargetOp && declareTargetOp.isDeclareTarget()) {
+      if (declareTargetOp.getDeclareTargetCaptureClause() ==
+              mlir::omp::DeclareTargetCaptureClause::link &&
+          declareTargetOp.getDeclareTargetDeviceType() !=
+              mlir::omp::DeclareTargetDeviceType::nohost) {
+        mapFlag |= llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_TO;
+        mapFlag |= llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_FROM;
+      }
+    } else if (fir::isa_trivial(varType) || fir::isa_char(varType)) {
+      // Scalars behave as if they were "firstprivate".
+      // TODO: Handle objects that are shared/lastprivate or were listed
+      // in an in_reduction clause.
+      if (isLiteralType(varType)) {
+        captureKind = mlir::omp::VariableCaptureKind::ByCopy;
+      } else {
+        mapFlag |= llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_TO;
+      }
+    } else if (!fir::isa_builtin_cptr_type(varType)) {
+      mapFlag |= llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_TO;
+      mapFlag |= llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_FROM;
+    }
+    return std::make_pair(mapFlag, captureKind);
+  }
+
+  switch (implicitBehaviour) {
+  case DefMap::ImplicitBehavior::Alloc:
+    return std::make_pair(llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_NONE,
+                          mlir::omp::VariableCaptureKind::ByRef);
+    break;
+  case DefMap::ImplicitBehavior::Firstprivate:
+  case DefMap::ImplicitBehavior::None:
+    TODO(loc, "Firstprivate and None are currently unsupported defaultmap "
+              "behaviour");
+    break;
+  case DefMap::ImplicitBehavior::From:
+    return std::make_pair(mapFlag |=
+                          llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_FROM,
+                          mlir::omp::VariableCaptureKind::ByRef);
+    break;
+  case DefMap::ImplicitBehavior::Present:
+    return std::make_pair(mapFlag |=
+                          llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_PRESENT,
+                          mlir::omp::VariableCaptureKind::ByRef);
+    break;
+  case DefMap::ImplicitBehavior::To:
+    return std::make_pair(mapFlag |=
+                          llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_TO,
+                          (fir::isa_trivial(varType) || fir::isa_char(varType))
+                              ? mlir::omp::VariableCaptureKind::ByCopy
+                              : mlir::omp::VariableCaptureKind::ByRef);
+    break;
+  case DefMap::ImplicitBehavior::Tofrom:
+    return std::make_pair(mapFlag |=
+                          llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_FROM |
+                          llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_TO,
+                          mlir::omp::VariableCaptureKind::ByRef);
+    break;
+  case DefMap::ImplicitBehavior::Default:
+    llvm_unreachable(
+        "Implicit None Behaviour Should Have Been Handled Earlier");
+    break;
+  }
+
+  return std::make_pair(mapFlag |=
+                        llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_FROM |
+                        llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_TO,
+                        mlir::omp::VariableCaptureKind::ByRef);
+}
+
 static mlir::omp::TargetOp
 genTargetOp(lower::AbstractConverter &converter, lower::SymMap &symTable,
             lower::StatementContext &stmtCtx,
@@ -2247,10 +2388,12 @@ genTargetOp(lower::AbstractConverter &converter, lower::SymMap &symTable,
     hostEvalInfo.emplace_back();
 
   mlir::omp::TargetOperands clauseOps;
+  DefaultMapsTy defaultMaps;
   llvm::SmallVector<const semantics::Symbol *> mapSyms, isDevicePtrSyms,
       hasDeviceAddrSyms;
   genTargetClauses(converter, semaCtx, symTable, stmtCtx, eval, item->clauses,
-                   loc, clauseOps, hasDeviceAddrSyms, isDevicePtrSyms, mapSyms);
+                   loc, clauseOps, defaultMaps, hasDeviceAddrSyms,
+                   isDevicePtrSyms, mapSyms);
 
   DataSharingProcessor dsp(converter, semaCtx, item->clauses, eval,
                            /*shouldCollectPreDeterminedSymbols=*/
@@ -2258,21 +2401,6 @@ genTargetOp(lower::AbstractConverter &converter, lower::SymMap &symTable,
                            /*useDelayedPrivatization=*/true, symTable);
   dsp.processStep1(&clauseOps);
 
-  // Check if a value of type `type` can be passed to the kernel by value.
-  // All kernel parameters are of pointer type, so if the value can be
-  // represented inside of a pointer, then it can be passed by value.
-  auto isLiteralType = [&](mlir::Type type) {
-    const mlir::DataLayout &dl = firOpBuilder.getDataLayout();
-    mlir::Type ptrTy =
-        mlir::LLVM::LLVMPointerType::get(&converter.getMLIRContext());
-    uint64_t ptrSize = dl.getTypeSize(ptrTy);
-    uint64_t ptrAlign = dl.getTypePreferredAlignment(ptrTy);
-
-    auto [size, align] = fir::getTypeSizeAndAlignmentOrCrash(
-        loc, type, dl, converter.getKindMap());
-    return size <= ptrSize && align <= ptrAlign;
-  };
-
   // 5.8.1 Implicit Data-Mapping Attribute Rules
   // The following code follows the implicit data-mapping rules to map all the
   // symbols used inside the region that do not have explicit data-environment
@@ -2334,56 +2462,25 @@ genTargetOp(lower::AbstractConverter &converter, lower::SymMap &symTable,
               firOpBuilder, info, dataExv,
               semantics::IsAssumedSizeArray(sym.GetUltimate()),
               converter.getCurrentLocation());
-
-      llvm::omp::OpenMPOffloadMappingFlags mapFlag =
-          llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_IMPLICIT;
-      mlir::omp::VariableCaptureKind captureKind =
-          mlir::omp::VariableCaptureKind::ByRef;
-
       mlir::Value baseOp = info.rawInput;
       mlir::Type eleType = baseOp.getType();
       if (auto refType = mlir::dyn_cast<fir::ReferenceType>(baseOp.getType()))
         eleType = refType.getElementType();
 
-      // If a variable is specified in declare target link and if device
-      // type is not specified as `nohost`, it needs to be mapped tofrom
-      mlir::ModuleOp mod = firOpBuilder.getModule();
-      mlir::Operation *op = mod.lookupSymbol(converter.mangleName(sym));
-      auto declareTargetOp =
-          llvm::dyn_cast_if_present<mlir::omp::DeclareTargetInterface>(op);
-      if (declareTargetOp && declareTargetOp.isDeclareTarget()) {
-        if (declareTargetOp.getDeclareTargetCaptureClause() ==
-                mlir::omp::DeclareTargetCaptureClause::link &&
-            declareTargetOp.getDeclareTargetDeviceType() !=
-                mlir::omp::DeclareTargetDeviceType::nohost) {
-          mapFlag |= llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_TO;
-          mapFlag |= llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_FROM;
-        }
-      } else if (fir::isa_trivial(eleType) || fir::isa_char(eleType)) {
-        // Scalars behave as if they were "firstprivate".
-        // TODO: Handle objects that are shared/lastprivate or were listed
-        // in an in_reduction clause.
-        if (isLiteralType(eleType)) {
-          captureKind = mlir::omp::VariableCaptureKind::ByCopy;
-        } else {
-          mapFlag |= llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_TO;
-        }
-      } else if (!fir::isa_builtin_cptr_type(eleType)) {
-        mapFlag |= llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_TO;
-        mapFlag |= llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_FROM;
-      }
-      auto location =
-          mlir::NameLoc::get(mlir::StringAttr::get(firOpBuilder.getContext(),
-                                                   sym.name().ToString()),
-                             baseOp.getLoc());
+      std::pair<llvm::omp::OpenMPOffloadMappingFlags,
+                mlir::omp::VariableCaptureKind>
+          mapFlagAndKind = getImplicitMapTypeAndKind(
+              firOpBuilder, converter, defaultMaps, eleType, loc, sym);
+
       mlir::Value mapOp = createMapInfoOp(
-          firOpBuilder, location, baseOp, /*varPtrPtr=*/mlir::Value{},
-          name.str(), bounds, /*members=*/{},
+          firOpBuilder, converter.getCurrentLocation(), baseOp,
+          /*varPtrPtr=*/mlir::Value{}, name.str(), bounds, /*members=*/{},
           /*membersIndex=*/mlir::ArrayAttr{},
           static_cast<
               std::underlying_type_t<llvm::omp::OpenMPOffloadMappingFlags>>(
-              mapFlag),
-          captureKind, baseOp.getType(), /*partialMap=*/false, mapperId);
+              std::get<0>(mapFlagAndKind)),
+          std::get<1>(mapFlagAndKind), baseOp.getType(),
+          /*partialMap=*/false, mapperId);
 
       clauseOps.mapVars.push_back(mapOp);
       mapSyms.push_back(&sym);
@@ -4062,6 +4159,7 @@ static void genOMP(lower::AbstractConverter &converter, lower::SymMap &symTable,
         !std::holds_alternative<clause::Copyin>(clause.u) &&
         !std::holds_alternative<clause::Copyprivate>(clause.u) &&
         !std::holds_alternative<clause::Default>(clause.u) &&
+        !std::holds_alternative<clause::Defaultmap>(clause.u) &&
         !std::holds_alternative<clause::Depend>(clause.u) &&
         !std::holds_alternative<clause::Filter>(clause.u) &&
         !std::holds_alternative<clause::Final>(clause.u) &&
diff --git a/flang/lib/Parser/openmp-parsers.cpp b/flang/lib/Parser/openmp-parsers.cpp
index bfca4e3f1730a..202c38696eaa5 100644
--- a/flang/lib/Parser/openmp-parsers.cpp
+++ b/flang/lib/Parser/openmp-parsers.cpp
@@ -689,7 +689,7 @@ TYPE_PARSER(construct<OmpMapClause>(
 // [OpenMP 5.0]
 // 2.19.7.2 defaultmap(implicit-behavior[:variable-category])
 //  implicit-behavior -> ALLOC | TO | FROM | TOFROM | FIRSRTPRIVATE | NONE |
-//  DEFAULT
+//  DEFAULT | PRESENT
 //  variable-category -> ALL | SCALAR | AGGREGATE | ALLOCATABLE | POINTER
 TYPE_PARSER(construct<OmpDefaultmapClause>(
     construct<OmpDefaultmapClause::ImplicitBehavior>(
@@ -700,7 +700,8 @@ TYPE_PARSER(construct<OmpDefaultmapClause>(
         "FIRSTPRIVATE" >>
             pure(OmpDefaultmapClause::ImplicitBehavior::Firstprivate) ||
         "NONE" >> pure(OmpDefaultmapClause::ImplicitBehavior::None) ||
-        "DEFAULT" >> pure(OmpDefaultmapClause::ImplicitBehavior::Default)),
+        "DEFAULT" >> pure(OmpDefaultmapClause::ImplicitBehavior::Default) ||
+        "PRESENT" >> pure(OmpDefaultmapClause::ImplicitBehavior::Present)),
     maybe(":" >> nonemptyList(Parser<OmpDefaultmapClause::Modifier>{}))))
 
 TYPE_PARSER(construct<OmpScheduleClause::Kind>(
diff --git a/flang/test/Lower/OpenMP/Todo/defaultmap-clause-firstprivate.f90 b/flang/test/Lower/OpenMP/Todo/defaultmap-clause-firstprivate.f90
new file mode 100644
index 0000000000000..0af2c7f5ea818
--- /dev/null
+++ b/flang/test/Lower/OpenMP/Todo/defaultmap-clause-firstprivate.f90
@@ -0,0 +1,11 @@
+!RUN: %not_todo_cmd bbc -emit-hlfir -fopenmp -fopenmp-version=51 -o - %s 2>&1 | FileCheck %s
+!RUN: %not_todo_cmd %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=51 -o - %s 2>&1 | FileCheck %s
+
+subroutine f00
+    implicit none
+    integer :: i
+    !CHECK: not yet implemented: Firstprivate and None are currently unsupported defaultmap behaviour
+    !$omp target defaultmap(firstprivate)
+      i = 10
+    !$omp end target
+  end
diff --git a/flang/test/Lower/OpenMP/Todo/defaultmap-clause-none.f90 b/flang/test/Lower/OpenMP/Todo/defaultmap-clause-none.f90
new file mode 100644
index 0000000000000..287eb4a9dfe8f
--- /dev/null
+++ b/flang/test/Lower/OpenMP/Todo/defaultmap-clause-none.f90
@@ -0,0 +1,11 @@
+!RUN: %not_todo_cmd bbc -emit-hlfir -fopenmp -fopenmp-version=51 -o - %s 2>&1 | FileCheck %s
+!RUN: %not_todo_cmd %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=51 -o - %s 2>&1 | FileCheck %s
+
+subroutine f00
+  implicit none
+  integer :: i
+  !CHECK: not yet implemented: Firstprivate and None are currently unsupported defaultmap behaviour
+  !$omp target defaultmap(none)
+    i = 10
+  !$omp end target
+end
diff --git a/flang/test/Lower/OpenMP/Todo/defaultmap-clause.f90 b/flang/test/Lower/OpenMP/Todo/defaultmap-clause.f90
deleted file mode 100644
index 062399d9a1944..0000000000000
--- a/flang/test/Lower/OpenMP/Todo/defaultmap-clause.f90
+++ /dev/null
@@ -1,8 +0,0 @@
-!RUN: %not_todo_cmd bbc -emit-hlfir -fopenmp -fopenmp-version=45 -o - %s 2>&1 | FileCheck %s
-!RUN: %not_todo_cmd %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=45 -o - %s 2>&1 | FileCheck %s
-
-!CHECK: not yet implemented: DEFAULTMAP clause is not implemented yet
-subroutine f00
-  !$omp target defaultmap(tofrom:scalar)
-  !$omp end target
-end
diff --git a/flang/test/Lower/OpenMP/defaultmap.f90 b/flang/test/Lower/OpenMP/defaultmap.f90
new file mode 100644
index 0000000000000..89d86ac1b8cc9
--- /dev/null
+++ b/flang/test/Lower/OpenMP/defaultmap.f90
@@ -0,0 +1,105 @@
+!RUN: %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=52 %s -o - | FileCheck %s
+
+subroutine defaultmap_allocatable_present()
+    implicit none
+    integer, dimension(:), allocatable :: arr
+
+! CHECK: %[[MAP_1:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>, i32) map_clauses(implicit, present, exit_release_or_enter_alloc) capture(ByRef) var_ptr_ptr({{.*}}) bounds({{.*}}) -> !fir.llvm_ptr<!fir.ref<!fir.array<?xi32>>> {name = ""}
+! CHECK: %[[MAP_2:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>, !fir.box<!fir.heap<!fir.array<?xi32>>>) map_clauses(implicit, to) capture(ByRef) members({{.*}}) -> !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>> {name = "arr"}
+!$omp target defaultmap(present: allocatable)
+    arr(1) = 10
+!$omp end target
+
+    return
+end subroutine
+
+subroutine defaultmap_scalar_tofrom()
+    implicit none
+    integer :: scalar_int
+
+! CHECK: %[[MAP:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<i32>, i32) map_clauses(implicit, tofrom) capture(ByRef) -> !fir.ref<i32> {name = "scalar_int"}
+   !$omp target defaultmap(tofrom: scalar)
+        scalar_int = 20
+   !$omp end target
+
+    return
+end subroutine
+
+subroutine defaultmap_all_default()
+    implicit none
+    integer, dimension(:), allocatable :: arr
+    integer :: aggregate(16)
+    integer :: scalar_int
+
+! CHECK: %[[MAP_1:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<i32>, i32) map_clauses(implicit, exit_release_or_enter_alloc) capture(ByCopy) -> !fir.ref<i32> {name = "scalar_int"}
+! CHECK: %[[MAP_2:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>, i32) map_clauses(implicit, tofrom) capture(ByRef) var_ptr_ptr({{.*}}) bounds({{.*}}) -> !fir.llvm_ptr<!fir.ref<!fir.array<?xi32>>> {name = ""}
+! CHECK: %[[MAP_3:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>, !fir.box<!fir.heap<!fir.array<?xi32>>>) map_clauses(implicit, to) capture(ByRef) members({{.*}}) -> !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>> {name = "arr"}
+! CHECK: %[[MAP_4:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<!fir.array<16xi32>>, !fir.array<16xi32>) map_clauses(implicit, tofrom) capture(ByRef) bounds({{.*}}) -> !fir.ref<!fir.array<16xi32>> {name = "aggregate"}
+
+   !$omp target defaultmap(default: all)
+        scalar_int = 20
+        arr(1) = scalar_int + aggregate(1)
+   !$omp end target
+
+    return
+end subroutine
+
+subroutine defaultmap_pointer_to()
+    implicit none
+    integer, dimension(:), pointer :: arr_ptr(:)
+    integer :: scalar_int
+
+! CHECK: %[[MAP_1:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xi32>>>>, i32) map_clauses(implicit, to) capture(ByRef) var_ptr_ptr({{.*}}) bounds({{.*}}) -> !fir.llvm_ptr<!fir.ref<!fir.array<?xi32>>> {name = ""}
+! CHECK: %[[MAP_2:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xi32>>>>, !fir.box<!fir.ptr<!fir.array<?xi32>>>) map_clauses(implicit, to) capture(ByRef) members({{.*}}) -> !fir.ref<!fir.box<!fir.ptr<!fir.array<?xi32>>>> {name = "arr_ptr"}
+! CHECK: %[[MAP_3:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<i32>, i32) map_clauses(implicit, exit_release_or_enter_alloc) capture(ByCopy) -> !fir.ref<i32> {name = "scalar_int"}
+    !$omp target defaultmap(to: pointer)
+        arr_ptr(1) = scalar_int + 20
+    !$omp end target
+
+    return
+end subroutine
+
+subroutine defaultmap_scalar_from()
+    implicit none
+    integer :: scalar_test
+
+! CHECK:%[[MAP:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<i32>, i32) map_clauses(implicit, from) capture(ByRef) -> !fir.ref<i32> {name = "scalar_test"}
+    !$omp target defaultmap(from: scalar)
+        scalar_test = 20
+    !$omp end target
+
+    return
+end subroutine
+
+subroutine defaultmap_aggregate_to()
+    implicit none
+    integer :: aggregate_arr(16)
+    integer :: scalar_test
+
+! CHECK: %[[MAP_1:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<i32>, i32) map_clauses(tofrom) capture(ByRef) -> !fir.ref<i32> {name = "scalar_test"}
+! CHECK: %[[MAP_2:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<!fir.array<16xi32>>, !fir.array<16xi32>) map_clauses(implicit, to) capture(ByRef) bounds({{.*}}) -> !fir.ref<!fir.array<16xi32>> {name = "aggregate_arr"}
+    !$omp target map(tofrom: scalar_test) defaultmap(to: aggregate)
+        aggregate_arr(1) = 1
+        scalar_test = 1
+    !$omp end target
+
+    return
+end subroutine
+
+subroutine defaultmap_dtype_aggregate_to()
+    implicit none
+    type :: dtype
+        integer(4) :: array_i(10)
+        integer(4) :: k
+    end type dtype
+
+    type(dtype) :: aggregate_type
+
+! CHECK: %[[MAP:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<!fir.type<_QFdefaultmap_dtype_aggregate_toTdtype{array_i:!fir.array<10xi32>,k:i32}>>, !fir.type<_QFdefaultmap_dtype_aggregate_toTdtype{array_i:!fir.array<10xi32>,k:i32}>) map_clauses(implicit, to) capture(ByRef) -> !fir.ref<!fir.type<_QFdefaultmap_dtype_aggregate_toTdtype{array_i:!fir.array<10xi32>,k:i32}>> {name = "aggregate_type"}
+    !$omp target defaultmap(to: aggregate)
+        aggregate_type%k = 40
+        aggregate_type%array_i(1) = 50
+    !$omp end target
+
+    return
+end subroutine
diff --git a/flang/test/Parser/OpenMP/defaultmap-clause.f90 b/flang/test/Parser/OpenMP/defaultmap-clause.f90
index dc036aedcd003..d908258fac763 100644
--- a/flang/test/Parser/OpenMP/defaultmap-clause.f90
+++ b/flang/test/Parser/OpenMP/defaultmap-clause.f90
@@ -82,3 +82,19 @@ subroutine f04
 !PARSE-TREE: | OmpClauseList -> OmpClause -> Defaultmap -> OmpDefaultmapClause
 !PARSE-TREE: | | ImplicitBehavior = Tofrom
 !PARSE-TREE: | | Modifier -> OmpVariableCategory -> Value  = Scalar
+
+subroutine f05
+  !$omp target defaultmap(present: scalar)
+  !$omp end target
+end
+
+!UNPARSE: SUBROUTINE f05
+!UNPARSE: !$OMP TARGET  DEFAULTMAP(PRESENT:SCALAR)
+!UNPARSE: !$OMP END TARGET
+!UNPARSE: END SUBROUTINE
+
+!PARSE-TREE: OmpBeginBlockDirective
+!PARSE-TREE: | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | OmpClauseList -> OmpClause -> Defaultmap -> OmpDefaultmapClause
+!PARSE-TREE: | | ImplicitBehavior = Present
+!PARSE-TREE: | | Modifier -> OmpVariableCategory -> Value  = Scalar
diff --git a/offload/test/offloading/fortran/target-defaultmap-present.f90 b/offload/test/offloading/fortran/target-defaultmap-present.f90
new file mode 100644
index 0000000000000..3342db21f15c8
--- /dev/null
+++ b/offload/test/offloading/fortran/target-defaultmap-present.f90
@@ -0,0 +1,34 @@
+! This checks that the basic functionality of setting the implicit mapping
+! behaviour of a target region to present incurs the present behaviour for
+! the implicit map capture.
+! REQUIRES: flang, amdgpu
+! RUN: %libomptarget-compile-fortran-generic
+! RUN: %libomptarget-run-fail-generic 2>&1 \
+! RUN: | %fcheck-generic
+
+! NOTE: This should intentionally fatal error in omptarget as it's not
+! present, as is intended.
+subroutine target_data_not_present()
+    implicit none
+    double precision, dimension(:), allocatable :: arr
+    integer, parameter :: N = 16
+    integer :: i
+
+    allocate(arr(N))
+
+!$omp target defaultmap(present: allocatable)
+    do i = 1,N
+        arr(i) = 42.0d0
+    end do
+!$omp end target
+
+    deallocate(arr)
+    return
+end subroutine
+
+program map_present
+    implicit none
+    call target_data_not_present()
+end program
+
+!CHECK: omptarget message: device mapping required by 'present' map type modifier does not exist for host address{{.*}}
diff --git a/offload/test/offloading/fortran/target-defaultmap.f90 b/offload/test/offloading/fortran/target-defaultmap.f90
new file mode 100644
index 0000000000000..d7184371129d2
--- /dev/null
+++ b/offload/test/offloading/fortran/target-defaultmap.f90
@@ -0,0 +1,166 @@
+! Offloading test checking the use of the depend clause on the target construct
+! REQUIRES: flang, amdgcn-amd-amdhsa
+! UNSUPPORTED: nvptx64-nvidia-cuda
+! UNSUPPORTED: nvptx64-nvidia-cuda-LTO
+! UNSUPPORTED: aarch64-unknown-linux-gnu
+! UNSUPPORTED: aarch64-unknown-linux-gnu-LTO
+! UNSUPPORTED: x86_64-unknown-linux-gnu
+! UNSUPPORTED: x86_64-unknown-linux-gnu-LTO
+
+! RUN: %libomptarget-compile-fortran-run-and-check-generic
+subroutine defaultmap_allocatable_present()
+    implicit none
+    integer, dimension(:), allocatable :: arr
+    integer :: N = 16
+    integer :: i
+
+    allocate(arr(N))
+
+!$omp target enter data map(to: arr)
+
+!$omp target defaultmap(present: allocatable)
+    do i = 1,N
+        arr(i) = N + 40
+    end do
+!$omp end target
+
+!$omp target exit data map(from: arr)
+
+    print *, arr
+    deallocate(arr)
+
+    return
+end subroutine
+
+subroutine defaultmap_scalar_tofrom()
+    implicit none
+    integer :: scalar_int
+    scalar_int = 10
+
+   !$omp target defaultmap(tofrom: scalar)
+        scalar_int = 20
+   !$omp end target
+
+    print *, scalar_int
+    return
+end subroutine
+
+subroutine defaultmap_all_default()
+    implicit none
+    integer, dimension(:), allocatable :: arr
+    integer :: aggregate(16)
+    integer :: N = 16
+    integer :: i, scalar_int
+
+    allocate(arr(N))
+
+    scalar_int = 10
+    aggregate = scalar_int
+
+   !$omp target defaultmap(default: all)
+        scalar_int = 20
+        do i = 1,N
+            arr(i) = scalar_int + aggregate(i)
+        end do
+   !$omp end target
+
+    print *, scalar_int
+    print *, arr
+
+    deallocate(arr)
+    return
+end subroutine
+
+subroutine defaultmap_pointer_to()
+    implicit none
+    integer, dimension(:), pointer :: arr_ptr(:)
+    integer :: scalar_int, i
+    allocate(arr_ptr(10))
+    arr_ptr = 10
+    scalar_int = 20
+
+    !$omp target defaultmap(to: pointer)
+        do i = 1,10
+            arr_ptr(i) = scalar_int + 20
+        end do
+    !$omp end target
+
+    print *, arr_ptr
+    deallocate(arr_ptr)
+    return
+end subroutine
+
+subroutine defaultmap_scalar_from()
+    implicit none
+    integer :: scalar_test
+    scalar_test = 10
+    !$omp target defaultmap(from: scalar)
+        scalar_test = 20
+    !$omp end target
+
+    print *, scalar_test
+    return
+end subroutine
+
+subroutine defaultmap_aggregate_to()
+    implicit none
+    integer :: aggregate_arr(16)
+    integer :: i, scalar_test = 0
+    aggregate_arr = 0
+    !$omp target map(tofrom: scalar_test) defaultmap(to: aggregate)
+        do i = 1,16
+            aggregate_arr(i) = i
+            scalar_test = scalar_test + aggregate_arr(i)
+        enddo
+    !$omp end target
+
+    print *, scalar_test
+    print *, aggregate_arr
+    return
+end subroutine
+
+subroutine defaultmap_dtype_aggregate_to()
+    implicit none
+    type :: dtype
+        real(4) :: i
+        real(4) :: j
+        integer(4) :: array_i(10)
+        integer(4) :: k
+        integer(4) :: array_j(10)
+    end type dtype
+
+    type(dtype) :: aggregate_type
+
+    aggregate_type%k = 20
+    aggregate_type%array_i = 30
+
+    !$omp target defaultmap(to: aggregate)
+        aggregate_type%k = 40
+        aggregate_type%array_i(1) = 50
+    !$omp end target
+
+    print *, aggregate_type%k
+    print *, aggregate_type%array_i(1)
+    return
+end subroutine
+
+program map_present
+    implicit none
+! CHECK: 56 56 56 56 56 56 56 56 56 56 56 56 56 56 56 56
+    call defaultmap_allocatable_present()
+! CHECK: 20
+    call defaultmap_scalar_tofrom()
+! CHECK: 10
+! CHECK: 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30
+    call defaultmap_all_default()
+! CHECK: 10 10 10 10 10 10 10 10 10 10
+    call defaultmap_pointer_to()
+! CHECK: 20
+    call defaultmap_scalar_from()
+! CHECK: 136
+! CHECK: 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0
+    call defaultmap_aggregate_to()
+! CHECK: 20
+! CHECK: 30
+    call defaultmap_dtype_aggregate_to()
+end program



More information about the flang-commits mailing list