[Openmp-commits] [flang] [openmp] [mlir] [Flang][OpenMP] Initial mapping of Fortran pointers and allocatables for target devices (PR #71766)

via Openmp-commits openmp-commits at lists.llvm.org
Wed Nov 8 20:38:12 PST 2023


llvmbot wrote:


<!--LLVM PR SUMMARY COMMENT-->

@llvm/pr-subscribers-openmp

Author: None (agozillon)

<details>
<summary>Changes</summary>

This patch seeks to add an initial lowering for pointers and allocatable variables explicitly captured by implicit and explicit map in Flang OpenMP.

Currently the intention is to treat these types as a special case of OpenMP structure mapping as far as the runtime is concerned, where the box (descriptor information) is the holding container and the underlying pointer is contained within the container. The descriptor pointed to by the generated bounds provides all the data required to offload the pointer contained within the descriptor.

This patch series is composed of several changes:
- Special handling of PFT -> MLIR lowering for allocatables/pointers, essentially mapping the original symbol which is the descriptor and allocated data, and not the address of the data as given by the base address of the shared bounds generation infrastructure. We also toggle on a new boolean for omp.map_info when it is an allocatable/pointer to indicate the need for special lowering.  
- An addition to omp.map_info of a boolean variable is_fortran_allocatable, that indicates if the value being mapped is a fortran allocatable type (also pointer).
- An addition of a specialised omp.map_info lowering to HLFIR/FIR's CodeGen when lowering from FIR+OpenMP -> LLVM+OpenMP, that allows specialised lowering of the descriptor type so that it doesn't devolve into an opaque pointer, as we need the type. Unfortunately this specialised lowering of descriptor types is only available to FIR. The default OpenMP lowering for omp.map_info remains, it's just superseded for Flang with the FIR specific lowering. 
- The specialised lowering for these fortran allocatables/pointers from MLIR -> LLVM-IR, which effectively treats the descriptor and data pointer as a parent structure + member of mapping like Clang would for a structure with a member pointer, when both are explicitly mapped.
- A bunch of related runtime tests, minor changes to existing tests to incorporate new changes and new flang/mlir tests for the various stages of the compiler that were modified.

NOTE: This patch is broken into several commits currently (if it works as expected), each commits description has some further details on the changes incorporated within the commit, giving some of the reasoning behind the current decisions, so please do read the commits (possibly a more bite size way to parse the patch as well). The PR can be broken up into multiple patches, but I thought I'd try this method of having a stacked PR first, as it allows all of the changes to be co-located for initial discussion and giving a good overview. It's worth noting that a majority of the changes are just additions of further tests. 

---

Patch is 82.71 KiB, truncated to 20.00 KiB below, full version: https://github.com/llvm/llvm-project/pull/71766.diff


20 Files Affected:

- (modified) flang/lib/Lower/OpenMP.cpp (+21-4) 
- (modified) flang/lib/Optimizer/CodeGen/CodeGen.cpp (+45) 
- (modified) flang/test/Driver/OpenMP/map-types-and-sizes.f90 (+22-1) 
- (modified) flang/test/Lower/OpenMP/FIR/target.f90 (+1-1) 
- (added) flang/test/Lower/OpenMP/allocatable-array-bounds.f90 (+101) 
- (added) flang/test/Lower/OpenMP/allocatable-map.f90 (+16) 
- (modified) flang/test/Lower/OpenMP/target.f90 (+1-1) 
- (modified) mlir/include/mlir/Dialect/OpenMP/OpenMPOps.td (+5-1) 
- (modified) mlir/lib/Target/LLVMIR/Dialect/OpenMP/OpenMPToLLVMIRTranslation.cpp (+225-11) 
- (modified) mlir/test/Dialect/OpenMP/ops.mlir (+15) 
- (added) mlir/test/Target/LLVMIR/omptarget-fortran-allocatable-types-host.mlir (+374) 
- (added) openmp/libomptarget/test/offloading/fortran/allocatable-array-section-1d-bounds.f90 (+46) 
- (added) openmp/libomptarget/test/offloading/fortran/allocatable-array-section-3d-bounds.f90 (+44) 
- (added) openmp/libomptarget/test/offloading/fortran/allocatable-map-scopes.f95 (+66) 
- (added) openmp/libomptarget/test/offloading/fortran/pointer-scopes-enter-exit-map.f90 (+83) 
- (added) openmp/libomptarget/test/offloading/fortran/pointer-target-array-section-3d-bounds.f90 (+43) 
- (added) openmp/libomptarget/test/offloading/fortran/pointer-target-map-scopes.f95 (+64) 
- (added) openmp/libomptarget/test/offloading/fortran/target_enter_exit_allocatables.f90 (+44) 
- (added) openmp/libomptarget/test/offloading/fortran/target_enter_exit_array.f90 (+41) 
- (added) openmp/libomptarget/test/offloading/fortran/target_single_value_allocate.f90 (+26) 


``````````diff
diff --git a/flang/lib/Lower/OpenMP.cpp b/flang/lib/Lower/OpenMP.cpp
index c2568c629e521c1..96ad89b1e1b65c1 100644
--- a/flang/lib/Lower/OpenMP.cpp
+++ b/flang/lib/Lower/OpenMP.cpp
@@ -54,6 +54,9 @@ getOmpObjectSymbol(const Fortran::parser::OmpObject &ompObject) {
                     Fortran::parser::Unwrap<Fortran::parser::ArrayElement>(
                         designator)) {
               sym = GetFirstName(arrayEle->base).symbol;
+            } else if (auto *structComp = Fortran::parser::Unwrap<
+                           Fortran::parser::StructureComponent>(designator)) {
+              sym = structComp->component.symbol;
             } else if (const Fortran::parser::Name *name =
                            Fortran::semantics::getDesignatorNameIfDataRef(
                                designator)) {
@@ -1708,7 +1711,7 @@ createMapInfoOp(fir::FirOpBuilder &builder, mlir::Location loc,
                 mlir::Value baseAddr, std::stringstream &name,
                 mlir::SmallVector<mlir::Value> bounds, uint64_t mapType,
                 mlir::omp::VariableCaptureKind mapCaptureType, mlir::Type retTy,
-                bool isVal = false) {
+                bool isAllocatable = false, bool isVal = false) {
   mlir::Value val, varPtr, varPtrPtr;
   mlir::TypeAttr varType;
 
@@ -1730,6 +1733,10 @@ createMapInfoOp(fir::FirOpBuilder &builder, mlir::Location loc,
       builder.getIntegerAttr(builder.getIntegerType(64, false), mapType),
       builder.getAttr<mlir::omp::VariableCaptureKindAttr>(mapCaptureType),
       builder.getStringAttr(name.str()));
+
+  if (isAllocatable)
+    op.setIsFortranAllocatableAttr(builder.getBoolAttr(isAllocatable));
+
   return op;
 }
 
@@ -1798,6 +1805,13 @@ bool ClauseProcessor::processMap(
               converter, firOpBuilder, semanticsContext, stmtCtx, ompObject,
               clauseLocation, asFortran, bounds, treatIndexAsSection);
 
+          // Address of the descriptor, not the de-referenced data, currently
+          // required for later lowering to LLVM-IR
+          if (Fortran::semantics::IsAllocatableOrPointer(
+                  *getOmpObjectSymbol(ompObject)))
+            baseAddr =
+                converter.getSymbolAddress(*getOmpObjectSymbol(ompObject));
+
           // Explicit map captures are captured ByRef by default,
           // optimisation passes may alter this to ByCopy or other capture
           // types to optimise
@@ -1806,7 +1820,9 @@ bool ClauseProcessor::processMap(
               static_cast<
                   std::underlying_type_t<llvm::omp::OpenMPOffloadMappingFlags>>(
                   mapTypeBits),
-              mlir::omp::VariableCaptureKind::ByRef, baseAddr.getType());
+              mlir::omp::VariableCaptureKind::ByRef, baseAddr.getType(),
+              Fortran::semantics::IsAllocatableOrPointer(
+                  *getOmpObjectSymbol(ompObject)));
 
           mapOperands.push_back(mapOp);
           if (mapSymTypes)
@@ -2661,7 +2677,8 @@ genTargetOp(Fortran::lower::AbstractConverter &converter,
             static_cast<
                 std::underlying_type_t<llvm::omp::OpenMPOffloadMappingFlags>>(
                 mapFlag),
-            captureKind, baseOp.getType());
+            captureKind, baseOp.getType(),
+            Fortran::semantics::IsAllocatableOrPointer(sym));
 
         mapOperands.push_back(mapOp);
         mapSymTypes.push_back(baseOp.getType());
@@ -2686,7 +2703,7 @@ genTargetOp(Fortran::lower::AbstractConverter &converter,
           static_cast<
               std::underlying_type_t<llvm::omp::OpenMPOffloadMappingFlags>>(
               llvm::omp::OpenMPOffloadMappingFlags::OMP_MAP_IMPLICIT),
-          mlir::omp::VariableCaptureKind::ByCopy, val.getType(), true);
+          mlir::omp::VariableCaptureKind::ByCopy, val.getType(), false, true);
       mapOperands.push_back(mapOp);
     }
   };
diff --git a/flang/lib/Optimizer/CodeGen/CodeGen.cpp b/flang/lib/Optimizer/CodeGen/CodeGen.cpp
index 9eabacdc818f6f4..d0ac9ea262be81e 100644
--- a/flang/lib/Optimizer/CodeGen/CodeGen.cpp
+++ b/flang/lib/Optimizer/CodeGen/CodeGen.cpp
@@ -417,6 +417,46 @@ class FIROpAndTypeConversion : public FIROpConversion<FromOp> {
 };
 } // namespace
 
+namespace {
+// FIR Op specific conversion for MapInfoOp that overwrites the default OpenMP
+// Dialect lowering, this allows FIR specific lowering of types, required for
+// descriptors of allocatables currently.
+struct MapInfoOpConversion : public FIROpConversion<mlir::omp::MapInfoOp> {
+  using FIROpConversion::FIROpConversion;
+
+  mlir::LogicalResult
+  matchAndRewrite(mlir::omp::MapInfoOp curOp, OpAdaptor adaptor,
+                  mlir::ConversionPatternRewriter &rewriter) const override {
+    const mlir::TypeConverter *converter = getTypeConverter();
+
+    llvm::SmallVector<mlir::Type> resTypes;
+    if (failed(converter->convertTypes(curOp->getResultTypes(), resTypes)))
+      return mlir::failure();
+
+    // Copy attributes of the curOp except for the typeAttr which should
+    // be converted
+    llvm::SmallVector<mlir::NamedAttribute> newAttrs;
+    for (mlir::NamedAttribute attr : curOp->getAttrs()) {
+      if (auto typeAttr = mlir::dyn_cast<mlir::TypeAttr>(attr.getValue())) {
+        mlir::Type newAttr;
+        if (curOp.getIsFortranAllocatable()) {
+          newAttr = this->getBoxTypePair(typeAttr.getValue()).llvm;
+        } else {
+          newAttr = converter->convertType(typeAttr.getValue());
+        }
+        newAttrs.emplace_back(attr.getName(), mlir::TypeAttr::get(newAttr));
+      } else {
+        newAttrs.push_back(attr);
+      }
+    }
+
+    rewriter.replaceOpWithNewOp<mlir::omp::MapInfoOp>(
+        curOp, resTypes, adaptor.getOperands(), newAttrs);
+    return mlir::success();
+  }
+};
+} // namespace
+
 namespace {
 /// Lower `fir.address_of` operation to `llvm.address_of` operation.
 struct AddrOfOpConversion : public FIROpConversion<fir::AddrOfOp> {
@@ -3828,6 +3868,11 @@ class FIRToLLVMLowering
                                                                   options);
     mlir::populateFuncToLLVMConversionPatterns(typeConverter, pattern);
     mlir::populateOpenMPToLLVMConversionPatterns(typeConverter, pattern);
+
+    // Insert OpenMP FIR specific conversion patterns that override OpenMP
+    // dialect default conversion patterns.
+    pattern.insert<MapInfoOpConversion>(typeConverter, options);
+
     mlir::arith::populateArithToLLVMConversionPatterns(typeConverter, pattern);
     mlir::cf::populateControlFlowToLLVMConversionPatterns(typeConverter,
                                                           pattern);
diff --git a/flang/test/Driver/OpenMP/map-types-and-sizes.f90 b/flang/test/Driver/OpenMP/map-types-and-sizes.f90
index e4f429e479af158..aa7e0042860296b 100644
--- a/flang/test/Driver/OpenMP/map-types-and-sizes.f90
+++ b/flang/test/Driver/OpenMP/map-types-and-sizes.f90
@@ -22,7 +22,6 @@ subroutine mapType_array
   !$omp end target
 end subroutine mapType_array
 
-!CHECK: @.offload_sizes{{.*}} = private unnamed_addr constant [1 x i64] [i64 8]
 !CHECK: @.offload_maptypes{{.*}} = private unnamed_addr constant [1 x i64] [i64 547]
 subroutine mapType_ptr
   integer, pointer :: a
@@ -31,6 +30,16 @@ subroutine mapType_ptr
   !$omp end target
 end subroutine mapType_ptr
 
+!CHECK: @.offload_maptypes{{.*}} = private unnamed_addr constant [1 x i64] [i64 547]
+subroutine mapType_allocatable
+  integer, allocatable :: a
+  allocate(a)
+  !$omp target
+     a = 10
+  !$omp end target
+  deallocate(a)
+end subroutine mapType_allocatable
+
 !CHECK: @.offload_sizes{{.*}} = private unnamed_addr constant [2 x i64] [i64 8, i64 4]
 !CHECK: @.offload_maptypes{{.*}} = private unnamed_addr constant [2 x i64] [i64 544, i64 800]
 subroutine mapType_c_ptr
@@ -50,3 +59,15 @@ subroutine mapType_char
      a = 'b'
   !$omp end target
 end subroutine mapType_char
+
+!CHECK-LABEL: define void @maptype_ptr_() {
+!CHECK: %[[DESC_ELE_SIZE:.*]] = getelementptr { ptr, i64, i32, i8, i8, i8, i8 }, ptr %{{.*}}, i64 0, i32 1
+!CHECK: %[[DESC_ELE_SIZE_LOAD:.*]] = load i64, ptr %[[DESC_ELE_SIZE]], align 8
+!CHECK: %[[OFFLOAD_SIZE_ARR:.*]] = getelementptr inbounds [1 x i64], ptr %.offload_sizes, i32 0, i32 0  
+!CHECK: store i64 %[[DESC_ELE_SIZE_LOAD]], ptr %[[OFFLOAD_SIZE_ARR]], align 8
+
+!CHECK-LABEL: define void @maptype_allocatable_() {
+!CHECK: %[[DESC_ELE_SIZE:.*]] = getelementptr { ptr, i64, i32, i8, i8, i8, i8 }, ptr %{{.*}}, i64 0, i32 1
+!CHECK: %[[DESC_ELE_SIZE_LOAD:.*]] = load i64, ptr %[[DESC_ELE_SIZE]], align 8
+!CHECK: %[[OFFLOAD_SIZE_ARR_1:.*]] = getelementptr inbounds [1 x i64], ptr %.offload_sizes, i32 0, i32 0  
+!CHECK: store i64 %[[DESC_ELE_SIZE_LOAD]], ptr %[[OFFLOAD_SIZE_ARR_1]], align 8
\ No newline at end of file
diff --git a/flang/test/Lower/OpenMP/FIR/target.f90 b/flang/test/Lower/OpenMP/FIR/target.f90
index d5a8fb242de9219..cd5326f3224e220 100644
--- a/flang/test/Lower/OpenMP/FIR/target.f90
+++ b/flang/test/Lower/OpenMP/FIR/target.f90
@@ -316,7 +316,7 @@ end subroutine omp_target_device_ptr
  subroutine omp_target_device_addr
    integer, pointer :: a
    !CHECK: %[[VAL_0:.*]] = fir.alloca !fir.box<!fir.ptr<i32>> {bindc_name = "a", uniq_name = "_QFomp_target_device_addrEa"}
-   !CHECK: %[[MAP:.*]] = omp.map_info var_ptr({{.*}})   map_clauses(tofrom) capture(ByRef) -> {{.*}} {name = "a"}
+   !CHECK: %[[MAP:.*]] = omp.map_info var_ptr({{.*}})   map_clauses(tofrom) capture(ByRef) -> {{.*}} {is_fortran_allocatable = true, name = "a"}
    !CHECK: omp.target_data map_entries(%[[MAP]] : {{.*}}) use_device_addr(%[[VAL_0]] : !fir.ref<!fir.box<!fir.ptr<i32>>>) {
    !$omp target data map(tofrom: a) use_device_addr(a)
    !CHECK: ^bb0(%[[VAL_1:.*]]: !fir.ref<!fir.box<!fir.ptr<i32>>>):
diff --git a/flang/test/Lower/OpenMP/allocatable-array-bounds.f90 b/flang/test/Lower/OpenMP/allocatable-array-bounds.f90
new file mode 100644
index 000000000000000..aa2649632a87270
--- /dev/null
+++ b/flang/test/Lower/OpenMP/allocatable-array-bounds.f90
@@ -0,0 +1,101 @@
+!RUN: %flang_fc1 -emit-hlfir -fopenmp %s -o - | FileCheck %s --check-prefixes HOST
+
+!HOST-LABEL:  func.func @_QPread_write_section() {
+
+!HOST: %[[ALLOCA_1:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<?xi32>>> {bindc_name = "sp_read", uniq_name = "_QFread_write_sectionEsp_read"}
+!HOST: %[[DECLARE_1:.*]]:2 = hlfir.declare %[[ALLOCA_1]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFread_write_sectionEsp_read"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>)
+
+!HOST: %[[ALLOCA_2:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<?xi32>>> {bindc_name = "sp_write", uniq_name = "_QFread_write_sectionEsp_write"}
+!HOST: %[[DECLARE_2:.*]]:2 = hlfir.declare %[[ALLOCA_2]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFread_write_sectionEsp_write"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>)
+
+!HOST: %[[LOAD_1:.*]] = fir.load %[[DECLARE_1]]#1 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>
+!HOST: %[[LOAD_2:.*]] = fir.load %[[DECLARE_1]]#1 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>
+!HOST: %[[CONSTANT_1:.*]] = arith.constant 0 : index
+!HOST: %[[BOX_1:.*]]:3 = fir.box_dims %[[LOAD_2]], %[[CONSTANT_1]] : (!fir.box<!fir.heap<!fir.array<?xi32>>>, index) -> (index, index, index)
+!HOST: %[[CONSTANT_2:.*]] = arith.constant 0 : index
+!HOST: %[[BOX_2:.*]]:3 = fir.box_dims %[[LOAD_1]], %[[CONSTANT_2]] : (!fir.box<!fir.heap<!fir.array<?xi32>>>, index) -> (index, index, index)
+!HOST: %[[CONSTANT_3:.*]] = arith.constant 2 : index
+!HOST: %[[LB_1:.*]] = arith.subi %[[CONSTANT_3]], %[[BOX_1]]#0 : index
+!HOST: %[[CONSTANT_4:.*]] = arith.constant 5 : index
+!HOST: %[[UB_1:.*]] = arith.subi %[[CONSTANT_4]], %[[BOX_1]]#0 : index
+!HOST: %[[BOUNDS_1:.*]] = omp.bounds lower_bound(%[[LB_1]] : index) upper_bound(%[[UB_1]] : index) stride(%[[BOX_2]]#2 : index) start_idx(%[[BOX_1]]#0 : index) {stride_in_bytes = true}
+!HOST: %[[MAP_INFO_1:.*]] = omp.map_info var_ptr(%[[DECLARE_1]]#1 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>, !fir.box<!fir.heap<!fir.array<?xi32>>>) map_clauses(tofrom) capture(ByRef) bounds(%[[BOUNDS_1]]) -> !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>> {is_fortran_allocatable = true, name = "sp_read(2:5)"}
+    
+!HOST: %[[LOAD_3:.*]] = fir.load %[[DECLARE_2]]#1 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>
+!HOST: %[[LOAD_4:.*]] = fir.load %[[DECLARE_2]]#1 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>
+!HOST: %[[CONSTANT_5:.*]] = arith.constant 0 : index
+!HOST: %[[BOX_3:.*]]:3 = fir.box_dims %[[LOAD_4]], %[[CONSTANT_5]] : (!fir.box<!fir.heap<!fir.array<?xi32>>>, index) -> (index, index, index)
+!HOST: %[[CONSTANT_6:.*]] = arith.constant 0 : index
+!HOST: %[[BOX_4:.*]]:3 = fir.box_dims %[[LOAD_3]], %[[CONSTANT_6]] : (!fir.box<!fir.heap<!fir.array<?xi32>>>, index) -> (index, index, index)
+!HOST: %[[CONSTANT_7:.*]] = arith.constant 2 : index
+!HOST: %[[LB_2:.*]] = arith.subi %[[CONSTANT_7]], %[[BOX_3]]#0 : index
+!HOST: %[[CONSTANT_8:.*]] = arith.constant 5 : index
+!HOST: %[[UB_2:.*]] = arith.subi %[[CONSTANT_8]], %[[BOX_3]]#0 : index
+!HOST: %[[BOUNDS_2:.*]] = omp.bounds lower_bound(%[[LB_2]] : index) upper_bound(%[[UB_2]] : index) stride(%[[BOX_4]]#2 : index) start_idx(%[[BOX_3]]#0 : index) {stride_in_bytes = true}
+!HOST: %[[MAP_INFO_2:.*]] = omp.map_info var_ptr(%11#1 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>, !fir.box<!fir.heap<!fir.array<?xi32>>>) map_clauses(tofrom) capture(ByRef) bounds(%[[BOUNDS_2]]) -> !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>> {is_fortran_allocatable = true, name = "sp_write(2:5)"}
+subroutine read_write_section()
+    integer, allocatable :: sp_read(:)
+    integer, allocatable :: sp_write(:)
+    allocate(sp_read(10)) 
+    allocate(sp_write(10))
+    sp_write = (/0,0,0,0,0,0,0,0,0,0/)
+    sp_read = (/1,2,3,4,5,6,7,8,9,10/)
+
+!$omp target map(tofrom:sp_read(2:5)) map(tofrom:sp_write(2:5))
+    do i = 2, 5
+        sp_write(i) = sp_read(i)
+    end do
+!$omp end target
+end subroutine read_write_section
+
+module assumed_allocatable_array_routines
+    contains
+
+!HOST-LABEL: func.func @_QMassumed_allocatable_array_routinesPassumed_shape_array(
+
+!HOST: %[[DECLARE:.*]]:2 = hlfir.declare %[[ARG:.*]] {fortran_attrs = #fir.var_attrs<allocatable, intent_inout>, uniq_name = "_QMassumed_allocatable_array_routinesFassumed_shape_arrayEarr_read_write"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>)
+!HOST: %[[LOAD_1:.*]] = fir.load %[[DECLARE]]#1 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>
+!HOST: %[[LOAD_2:.*]] = fir.load %[[DECLARE]]#1 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>
+!HOST: %[[CONSTANT_1:.*]] = arith.constant 0 : index
+!HOST: %[[BOX_1:.*]]:3 = fir.box_dims %[[LOAD_2]], %[[CONSTANT_1]] : (!fir.box<!fir.heap<!fir.array<?xi32>>>, index) -> (index, index, index)
+!HOST: %[[CONSTANT_2:.*]] = arith.constant 0 : index
+!HOST: %[[BOX_2:.*]]:3 = fir.box_dims %[[LOAD_1]], %[[CONSTANT_2]] : (!fir.box<!fir.heap<!fir.array<?xi32>>>, index) -> (index, index, index)
+!HOST: %[[CONSTANT_3:.*]] = arith.constant 2 : index
+!HOST: %[[LB:.*]] = arith.subi %[[CONSTANT_3]], %[[BOX_1]]#0 : index
+!HOST: %[[CONSTANT_4:.*]] = arith.constant 5 : index
+!HOST: %[[UB:.*]] = arith.subi %[[CONSTANT_4]], %[[BOX_1]]#0 : index
+!HOST: %[[BOUNDS:.*]] = omp.bounds lower_bound(%[[LB]] : index) upper_bound(%[[UB]] : index) stride(%[[BOX_2]]#2 : index) start_idx(%[[BOX_1]]#0 : index) {stride_in_bytes = true}
+!HOST: %[[MAP_INFO:.*]] = omp.map_info var_ptr(%[[DECLARE]]#1 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>, !fir.box<!fir.heap<!fir.array<?xi32>>>) map_clauses(tofrom) capture(ByRef) bounds(%[[BOUNDS]]) -> !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>> {is_fortran_allocatable = true, name = "arr_read_write(2:5)"}
+subroutine assumed_shape_array(arr_read_write)
+    integer, allocatable, intent(inout) :: arr_read_write(:)
+
+!$omp target map(tofrom:arr_read_write(2:5))
+    do i = 2, 5
+        arr_read_write(i) = i
+    end do
+!$omp end target
+end subroutine assumed_shape_array
+end module assumed_allocatable_array_routines
+
+!HOST-LABEL: func.func @_QPcall_assumed_shape_and_size_array() {
+!HOST: %[[ALLOCA:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<?xi32>>> {bindc_name = "arr_read_write", uniq_name = "_QFcall_assumed_shape_and_size_arrayEarr_read_write"}
+!HOST: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFcall_assumed_shape_and_size_arrayEarr_read_write"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>)
+!HOST: %[[ALLOCA_MEM:.*]] = fir.allocmem !fir.array<?xi32>, %{{.*}} {fir.must_be_heap = true, uniq_name = "_QFcall_assumed_shape_and_size_arrayEarr_read_write.alloc"}
+!HOST: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1>
+!HOST: %[[EMBOX:.*]] = fir.embox %[[ALLOCA_MEM]](%[[SHAPE]]) : (!fir.heap<!fir.array<?xi32>>, !fir.shape<1>) -> !fir.box<!fir.heap<!fir.array<?xi32>>>
+!HOST: fir.store %[[EMBOX]] to %[[DECLARE]]#1 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>
+!HOST: %[[LOAD:.*]] = fir.load %[[DECLARE]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>
+!HOST: %[[CONSTANT_1:.*]] = arith.constant 10 : index
+!HOST: %[[CONSTANT_2:.*]] = arith.constant 20 : index
+!HOST: %[[CONSTANT_3:.*]] = arith.constant 1 : index
+!HOST: %[[CONSTANT_4:.*]] = arith.constant 11 : index
+!HOST: %[[SHAPE:.*]] = fir.shape %[[CONSTANT_4]] : (index) -> !fir.shape<1>
+!HOST: %[[DESIGNATE:.*]] = hlfir.designate %[[LOAD]] (%[[CONSTANT_1]]:%[[CONSTANT_2]]:%[[CONSTANT_3]])  shape %[[SHAPE]] : (!fir.box<!fir.heap<!fir.array<?xi32>>>, index, index, index, !fir.shape<1>) -> !fir.ref<!fir.array<11xi32>>
+!HOST: fir.call @_QPassumed_size_array(%[[DESIGNATE]]) fastmath<contract> : (!fir.ref<!fir.array<11xi32>>) -> ()
+subroutine call_assumed_shape_and_size_array
+    use assumed_allocatable_array_routines
+    integer, allocatable :: arr_read_write(:)
+    allocate(arr_read_write(20))
+    call assumed_size_array(arr_read_write(10:20))
+    deallocate(arr_read_write)
+end subroutine call_assumed_shape_and_size_array
diff --git a/flang/test/Lower/OpenMP/allocatable-map.f90 b/flang/test/Lower/OpenMP/allocatable-map.f90
new file mode 100644
index 000000000000000..7d10ff181d76e05
--- /dev/null
+++ b/flang/test/Lower/OpenMP/allocatable-map.f90
@@ -0,0 +1,16 @@
+!RUN: %flang_fc1 -emit-hlfir -fopenmp %s -o - | FileCheck %s --check-prefixes="HLFIRDIALECT"
+!RUN: %flang_fc1 -emit-fir -fopenmp %s -o - | fir-opt --fir-to-llvm-ir | FileCheck %s --check-prefixes="LLVMOMPDIALECT"
+
+!LLVMOMPDIALECT: %[[ALLOCA:.*]] = llvm.alloca {{.*}} x !llvm.struct<(ptr, i64, i32, i8, i8, i8, i8)> {bindc_name = "point"} : (i64) -> !llvm.ptr
+!LLVMOMPDIALECT: %[[MAP:.*]] = omp.map_info var_ptr(%[[ALLOCA]] : !llvm.ptr, !llvm.struct<(ptr, i64, i32, i8, i8, i8, i8)>) map_clauses(implicit, tofrom) capture(ByRef) -> !llvm.ptr {is_fortran_allocatable = true, name = "point"}
+!LLVMOMPDIALECT: omp.target map_entries({{.*}}, %[[MAP]] -> {{.*}} : {{.*}}, !llvm.ptr) {
+
+!HLFIRDIALECT: %[[POINTER:.*]]:2 = hlfir.declare %0 {fortran_attrs = #fir.var_attrs<pointer>, uniq_name = "_QFpointer_routineEpoint"} : (!fir.ref<!fir.box<!fir.ptr<i32>>>) -> (!fir.ref<!fir.box<!fir.ptr<i32>>>, !fir.ref<!fir.box<!fir.ptr<i32>>>)
+!HLFIRDIALECT: %[[POINTER_MAP:.*]] = omp.map_info var_ptr(%[[POINTER]]#1 : !fir.ref<!fir.box<!fir.ptr<i32>>>, !fir.box<!fir.ptr<i32>>) map_clauses(implicit, tofrom) capture(ByRef) -> !fir.ref<!fir.box<!fir.ptr<i32>>> {is_fortran_allocatable = true, name = "point"}
+!HLFIRDIALECT: omp.target map_entries({{.*}}, %[[POINTER_MAP]] -> {{.*}} : {{.*}}, !fir.ref<!fir.box<!fir.ptr<i32>>>) {
+subroutine pointer_routine()
+    integer, pointer :: point 
+!$omp target map(tofrom:pointer)
+    point = 1
+!$omp end target
+end subroutine pointer_routine
diff --git a/flang/test/Lower/OpenMP/target.f90 b/flang/test/Lower/OpenMP/target.f90
index 86f456b847df90a..a409769ae4f8bf4 100644
--- a/flang/test/Lower/OpenMP/target.f90
+++ b/flang/test/Lower/OpenMP/target.f90
@@ -340,7 +340,7 @@ subroutine omp_target_device_addr
  ...
[truncated]

``````````

</details>


https://github.com/llvm/llvm-project/pull/71766


More information about the Openmp-commits mailing list