[flang-commits] [flang] e39866c - [Flang][OpenMP][MLIR] Add lowering from PFT to MLIR (FIR) for OpenMP declare target directive in Flang

Andrew Gozillon via flang-commits flang-commits at lists.llvm.org
Mon Jun 5 05:08:13 PDT 2023


Author: Andrew Gozillon
Date: 2023-06-05T07:07:56-05:00
New Revision: e39866c75d9157dd2031af6189a8b6e605286f90

URL: https://github.com/llvm/llvm-project/commit/e39866c75d9157dd2031af6189a8b6e605286f90
DIFF: https://github.com/llvm/llvm-project/commit/e39866c75d9157dd2031af6189a8b6e605286f90.diff

LOG: [Flang][OpenMP][MLIR] Add lowering from PFT to MLIR (FIR) for OpenMP declare target directive in Flang

This patch adds PFT lowering for the OpenMP declare target directive
in Flang to the omp dialects declare target attribute, which currently
applies to function or global operations.

Reviewers: kiranchandramohan, skatrak, jsjodin

Differential Revision: https://reviews.llvm.org/D150329

Added: 
    flang/test/Lower/OpenMP/omp-declare-target-data.f90
    flang/test/Lower/OpenMP/omp-declare-target-func-and-subr.f90

Modified: 
    flang/lib/Lower/OpenMP.cpp

Removed: 
    flang/test/Lower/OpenMP/Todo/omp-declare-target.f90


################################################################################
diff  --git a/flang/lib/Lower/OpenMP.cpp b/flang/lib/Lower/OpenMP.cpp
index 96fd6762934f8..701504394ca97 100644
--- a/flang/lib/Lower/OpenMP.cpp
+++ b/flang/lib/Lower/OpenMP.cpp
@@ -2494,6 +2494,129 @@ void Fortran::lower::genThreadprivateOp(
   converter.bindSymbol(sym, symThreadprivateExv);
 }
 
+void handleDeclareTarget(Fortran::lower::AbstractConverter &converter,
+                         Fortran::lower::pft::Evaluation &eval,
+                         const Fortran::parser::OpenMPDeclareTargetConstruct
+                             &declareTargetConstruct) {
+  llvm::SmallVector<std::pair<mlir::omp::DeclareTargetCaptureClause,
+                              Fortran::semantics::Symbol>,
+                    0>
+      symbolAndClause;
+  mlir::ModuleOp mod = converter.getFirOpBuilder().getModule();
+
+  auto findFuncAndVarSyms = [&](const Fortran::parser::OmpObjectList &objList,
+                                mlir::omp::DeclareTargetCaptureClause clause) {
+    for (const Fortran::parser::OmpObject &ompObject : objList.v) {
+      Fortran::common::visit(
+          Fortran::common::visitors{
+              [&](const Fortran::parser::Designator &designator) {
+                if (const Fortran::parser::Name *name =
+                        getDesignatorNameIfDataRef(designator)) {
+                  symbolAndClause.push_back(
+                      std::make_pair(clause, *name->symbol));
+                }
+              },
+              [&](const Fortran::parser::Name &name) {
+                symbolAndClause.push_back(std::make_pair(clause, *name.symbol));
+              }},
+          ompObject.u);
+    }
+  };
+
+  // The default capture type
+  Fortran::parser::OmpDeviceTypeClause::Type deviceType =
+      Fortran::parser::OmpDeviceTypeClause::Type::Any;
+  const auto &spec = std::get<Fortran::parser::OmpDeclareTargetSpecifier>(
+      declareTargetConstruct.t);
+  if (const auto *objectList{
+          Fortran::parser::Unwrap<Fortran::parser::OmpObjectList>(spec.u)}) {
+    // Case: declare target(func, var1, var2)
+    findFuncAndVarSyms(*objectList, mlir::omp::DeclareTargetCaptureClause::to);
+  } else if (const auto *clauseList{
+                 Fortran::parser::Unwrap<Fortran::parser::OmpClauseList>(
+                     spec.u)}) {
+    if (clauseList->v.empty()) {
+      // Case: declare target, implicit capture of function
+      symbolAndClause.push_back(
+          std::make_pair(mlir::omp::DeclareTargetCaptureClause::to,
+                         eval.getOwningProcedure()->getSubprogramSymbol()));
+    }
+
+    for (const Fortran::parser::OmpClause &clause : clauseList->v) {
+      if (const auto *toClause =
+              std::get_if<Fortran::parser::OmpClause::To>(&clause.u)) {
+        // Case: declare target to(func, var1, var2)...
+        findFuncAndVarSyms(toClause->v,
+                           mlir::omp::DeclareTargetCaptureClause::to);
+      } else if (const auto *linkClause =
+                     std::get_if<Fortran::parser::OmpClause::Link>(&clause.u)) {
+        // Case: declare target link(var1, var2)...
+        findFuncAndVarSyms(linkClause->v,
+                           mlir::omp::DeclareTargetCaptureClause::link);
+      } else if (const auto *deviceClause =
+                     std::get_if<Fortran::parser::OmpClause::DeviceType>(
+                         &clause.u)) {
+        // Case: declare target ... device_type(any | host | nohost)
+        deviceType = deviceClause->v.v;
+      }
+    }
+  }
+
+  for (std::pair<mlir::omp::DeclareTargetCaptureClause,
+                 Fortran::semantics::Symbol>
+           symClause : symbolAndClause) {
+    mlir::Operation *op =
+        mod.lookupSymbol(converter.mangleName(std::get<1>(symClause)));
+    // There's several cases this can currently be triggered and it could be
+    // one of the following:
+    // 1) Invalid argument passed to a declare target that currently isn't
+    // captured by a frontend semantic check
+    // 2) The symbol of a valid argument is not correctly updated by one of
+    // the prior passes, resulting in missing symbol information
+    // 3) It's a variable internal to a module or program, that is legal by
+    // Fortran OpenMP standards, but is currently unhandled as they do not
+    // appear in the symbol table as they are represented as allocas
+    if (!op)
+      TODO(converter.getCurrentLocation(),
+           "Missing symbol, possible case of currently unsupported use of "
+           "a program local variable in declare target or erroneous symbol "
+           "information ");
+
+    auto declareTargetOp = dyn_cast<mlir::omp::DeclareTargetInterface>(op);
+    if (!declareTargetOp)
+      fir::emitFatalError(
+          converter.getCurrentLocation(),
+          "Attempt to apply declare target on unsupported operation");
+
+    mlir::omp::DeclareTargetDeviceType newDeviceType;
+    switch (deviceType) {
+    case Fortran::parser::OmpDeviceTypeClause::Type::Nohost:
+      newDeviceType = mlir::omp::DeclareTargetDeviceType::nohost;
+      break;
+    case Fortran::parser::OmpDeviceTypeClause::Type::Host:
+      newDeviceType = mlir::omp::DeclareTargetDeviceType::host;
+      break;
+    case Fortran::parser::OmpDeviceTypeClause::Type::Any:
+      newDeviceType = mlir::omp::DeclareTargetDeviceType::any;
+      break;
+    }
+
+    // The function or global already has a declare target applied to it,
+    // very likely through implicit capture (usage in another declare
+    // target function/subroutine). It should be marked as any if it has
+    // been assigned both host and nohost, else we skip, as there is no
+    // change
+    if (declareTargetOp.isDeclareTarget()) {
+      if (declareTargetOp.getDeclareTargetDeviceType() != newDeviceType)
+        declareTargetOp.setDeclareTarget(
+            mlir::omp::DeclareTargetDeviceType::any, std::get<0>(symClause));
+      continue;
+    }
+
+    declareTargetOp.setDeclareTarget(newDeviceType, std::get<0>(symClause));
+  }
+}
+
 void Fortran::lower::genOpenMPDeclarativeConstruct(
     Fortran::lower::AbstractConverter &converter,
     Fortran::lower::pft::Evaluation &eval,
@@ -2516,8 +2639,7 @@ void Fortran::lower::genOpenMPDeclarativeConstruct(
           },
           [&](const Fortran::parser::OpenMPDeclareTargetConstruct
                   &declareTargetConstruct) {
-            TODO(converter.getCurrentLocation(),
-                 "OpenMPDeclareTargetConstruct");
+            handleDeclareTarget(converter, eval, declareTargetConstruct);
           },
           [&](const Fortran::parser::OpenMPRequiresConstruct
                   &requiresConstruct) {

diff  --git a/flang/test/Lower/OpenMP/Todo/omp-declare-target.f90 b/flang/test/Lower/OpenMP/Todo/omp-declare-target.f90
deleted file mode 100644
index 4f904475cd497..0000000000000
--- a/flang/test/Lower/OpenMP/Todo/omp-declare-target.f90
+++ /dev/null
@@ -1,12 +0,0 @@
-! This test checks lowering of OpenMP declare target Directive.
-
-// RUN: not flang-new -fc1 -emit-fir -fopenmp %s 2>&1 | FileCheck %s
-
-module mod1
-contains
-  subroutine sub()
-    integer :: x, y
-    // CHECK: not yet implemented: OpenMPDeclareTargetConstruct
-    !$omp declare target
-  end
-end module

diff  --git a/flang/test/Lower/OpenMP/omp-declare-target-data.f90 b/flang/test/Lower/OpenMP/omp-declare-target-data.f90
new file mode 100644
index 0000000000000..2447f48c059c5
--- /dev/null
+++ b/flang/test/Lower/OpenMP/omp-declare-target-data.f90
@@ -0,0 +1,72 @@
+!RUN: %flang_fc1 -emit-fir -fopenmp %s -o - | FileCheck %s 
+!RUN: %flang_fc1 -emit-fir -fopenmp -fopenmp-is-device %s -o - | FileCheck %s
+
+module test_0
+    implicit none
+
+!CHECK-DAG: fir.global @_QMtest_0Edata_int {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (link)>} : i32
+INTEGER :: data_int = 10
+!$omp declare target link(data_int)
+
+!CHECK-DAG: fir.global @_QMtest_0Earray_1d({{.*}}) {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (link)>} : !fir.array<3xi32>
+INTEGER :: array_1d(3) = (/1,2,3/)
+!$omp declare target link(array_1d)
+
+!CHECK-DAG: fir.global @_QMtest_0Earray_2d({{.*}}) {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (link)>} : !fir.array<2x2xi32> 
+INTEGER :: array_2d(2,2) = reshape((/1,2,3,4/), (/2,2/))
+!$omp declare target link(array_2d)
+
+!CHECK-DAG: fir.global @_QMtest_0Ept1 {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (link)>} : !fir.box<!fir.ptr<i32>>
+INTEGER, POINTER :: pt1
+!$omp declare target link(pt1)
+
+!CHECK-DAG: fir.global @_QMtest_0Ept2_tar {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (link)>} target : i32
+INTEGER, TARGET :: pt2_tar = 5 
+!$omp declare target link(pt2_tar)
+
+!CHECK-DAG: fir.global @_QMtest_0Ept2 {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (link)>} : !fir.box<!fir.ptr<i32>>
+INTEGER, POINTER :: pt2 => pt2_tar
+!$omp declare target link(pt2)
+
+!CHECK-DAG: fir.global @_QMtest_0Edata_int_to {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>} : i32
+INTEGER :: data_int_to = 5
+!$omp declare target to(data_int_to)
+
+!CHECK-DAG: fir.global @_QMtest_0Edata_int_clauseless {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>} : i32
+INTEGER :: data_int_clauseless = 1
+!$omp declare target(data_int_clauseless)
+
+!CHECK-DAG: fir.global @_QMtest_0Edata_extended_to_1 {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>} : f32
+!CHECK-DAG: fir.global @_QMtest_0Edata_extended_to_2 {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>} : f32
+REAL :: data_extended_to_1 = 2
+REAL :: data_extended_to_2 = 3
+!$omp declare target to(data_extended_to_1, data_extended_to_2)
+
+!CHECK-DAG: fir.global @_QMtest_0Edata_extended_link_1 {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (link)>} : f32
+!CHECK-DAG: fir.global @_QMtest_0Edata_extended_link_2 {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (link)>} : f32
+REAL :: data_extended_link_1 = 2
+REAL :: data_extended_link_2 = 3
+!$omp declare target link(data_extended_link_1, data_extended_link_2)
+
+contains
+end module test_0
+
+PROGRAM commons
+    !CHECK-DAG: fir.global @_QCnumbers {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>} : tuple<f32, f32> {
+    REAL :: one = 1
+    REAL :: two = 2
+    COMMON /numbers/ one, two
+    !$omp declare target(/numbers/)
+    
+    !CHECK-DAG: fir.global @_QCnumbers_link {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (link)>} : tuple<f32, f32> {
+    REAL :: one_link = 1
+    REAL :: two_link = 2
+    COMMON /numbers_link/ one_link, two_link
+    !$omp declare target link(/numbers_link/)
+
+    !CHECK-DAG: fir.global @_QCnumbers_to {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>} : tuple<f32, f32> {
+    REAL :: one_to = 1
+    REAL :: two_to = 2
+    COMMON /numbers_to/ one_to, two_to
+    !$omp declare target to(/numbers_to/)
+END

diff  --git a/flang/test/Lower/OpenMP/omp-declare-target-func-and-subr.f90 b/flang/test/Lower/OpenMP/omp-declare-target-func-and-subr.f90
new file mode 100644
index 0000000000000..6e197c59b211b
--- /dev/null
+++ b/flang/test/Lower/OpenMP/omp-declare-target-func-and-subr.f90
@@ -0,0 +1,109 @@
+!RUN: %flang_fc1 -emit-fir -fopenmp %s -o - | FileCheck %s
+
+! Check specification valid forms of declare target with functions 
+! utilising device_type and to clauses as well as the default 
+! zero clause declare target
+
+! CHECK-LABEL: func.func @_QPfunc_t_device()
+! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>{{.*}}
+FUNCTION FUNC_T_DEVICE() RESULT(I)
+!$omp declare target to(FUNC_T_DEVICE) device_type(nohost)
+    INTEGER :: I
+    I = 1
+END FUNCTION FUNC_T_DEVICE
+
+! CHECK-LABEL: func.func @_QPfunc_t_host()
+! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (host), capture_clause = (to)>{{.*}}
+FUNCTION FUNC_T_HOST() RESULT(I)
+!$omp declare target to(FUNC_T_HOST) device_type(host)
+    INTEGER :: I
+    I = 1
+END FUNCTION FUNC_T_HOST
+
+! CHECK-LABEL: func.func @_QPfunc_t_any()
+! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
+FUNCTION FUNC_T_ANY() RESULT(I)
+!$omp declare target to(FUNC_T_ANY) device_type(any)
+    INTEGER :: I
+    I = 1
+END FUNCTION FUNC_T_ANY
+
+! CHECK-LABEL: func.func @_QPfunc_default_t_any()
+! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
+FUNCTION FUNC_DEFAULT_T_ANY() RESULT(I)
+!$omp declare target to(FUNC_DEFAULT_T_ANY)
+    INTEGER :: I
+    I = 1
+END FUNCTION FUNC_DEFAULT_T_ANY
+
+! CHECK-LABEL: func.func @_QPfunc_default_any()
+! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
+FUNCTION FUNC_DEFAULT_ANY() RESULT(I)
+!$omp declare target
+    INTEGER :: I
+    I = 1
+END FUNCTION FUNC_DEFAULT_ANY
+
+! CHECK-LABEL: func.func @_QPfunc_default_extendedlist()
+! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
+FUNCTION FUNC_DEFAULT_EXTENDEDLIST() RESULT(I)
+!$omp declare target(FUNC_DEFAULT_EXTENDEDLIST)
+    INTEGER :: I
+    I = 1
+END FUNCTION FUNC_DEFAULT_EXTENDEDLIST
+
+!! -----
+
+! Check specification valid forms of declare target with subroutines 
+! utilising device_type and to clauses as well as the default 
+! zero clause declare target
+
+! CHECK-LABEL: func.func @_QPsubr_t_device()
+! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>{{.*}}
+SUBROUTINE SUBR_T_DEVICE()
+!$omp declare target to(SUBR_T_DEVICE) device_type(nohost)
+END
+
+! CHECK-LABEL: func.func @_QPsubr_t_host()
+! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (host), capture_clause = (to)>{{.*}}
+SUBROUTINE SUBR_T_HOST()
+!$omp declare target to(SUBR_T_HOST) device_type(host)
+END
+
+! CHECK-LABEL: func.func @_QPsubr_t_any()
+! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
+SUBROUTINE SUBR_T_ANY()
+!$omp declare target to(SUBR_T_ANY) device_type(any)
+END
+
+! CHECK-LABEL: func.func @_QPsubr_default_t_any()
+! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
+SUBROUTINE SUBR_DEFAULT_T_ANY()
+!$omp declare target to(SUBR_DEFAULT_T_ANY)
+END
+
+! CHECK-LABEL: func.func @_QPsubr_default_any()
+! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
+SUBROUTINE SUBR_DEFAULT_ANY()
+!$omp declare target
+END
+
+! CHECK-LABEL: func.func @_QPsubr_default_extendedlist()
+! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
+SUBROUTINE SUBR_DEFAULT_EXTENDEDLIST()
+!$omp declare target(SUBR_DEFAULT_EXTENDEDLIST)
+END
+
+!! -----
+
+! CHECK-LABEL: func.func @_QPrecursive_declare_target
+! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>{{.*}}
+RECURSIVE FUNCTION RECURSIVE_DECLARE_TARGET(INCREMENT) RESULT(K)
+!$omp declare target to(RECURSIVE_DECLARE_TARGET) device_type(nohost)
+    INTEGER :: INCREMENT, K
+    IF (INCREMENT == 10) THEN
+        K = INCREMENT
+    ELSE
+        K = RECURSIVE_DECLARE_TARGET(INCREMENT + 1)
+    END IF
+END FUNCTION RECURSIVE_DECLARE_TARGET


        


More information about the flang-commits mailing list