Skip to content

Commit 2ca0cdf

Browse files
authored
Merge pull request #1109 from schweitzpgi/ch-speicher
Full implementation of lazy, ragged buffers for caching intermediate
2 parents 72e05cd + dad1185 commit 2ca0cdf

File tree

18 files changed

+1266
-689
lines changed

18 files changed

+1266
-689
lines changed

flang/include/flang/Lower/ConvertExpr.h

Lines changed: 13 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -169,28 +169,19 @@ createSomeArrayTempValue(AbstractConverter &converter,
169169
const evaluate::Expr<evaluate::SomeType> &expr,
170170
SymMap &symMap, StatementContext &stmtCtx);
171171

172-
// Lambda to reload the dynamically allocated pointers to a lazy buffer and its
173-
// extents. This is used to introduce these ssa-values in a place that will
174-
// dominate any/all subsequent uses after the loop that created the lazy buffer.
175-
using LoadLazyBufferLambda =
176-
std::function<std::pair<fir::ExtendedValue, mlir::Value>(
177-
fir::FirOpBuilder &)>;
178-
179-
// Creating a lazy array temporary returns a pair of values. The first is an
180-
// extended value which is a pointer to the buffer, of array type, with the
181-
// appropriate dynamic extents. The second argument is a continuation to reload
182-
// the buffer at some future point in the code gen.
183-
using CreateLazyArrayResult =
184-
std::pair<fir::ExtendedValue, LoadLazyBufferLambda>;
185-
186-
/// Like createSomeArrayTempValue, but the temporary buffer is allocated lazily
187-
/// (inside the loops instead of before the loops). This can be useful if a
188-
/// loop's bounds are functions of other loop indices, for example.
189-
CreateLazyArrayResult
190-
createLazyArrayTempValue(AbstractConverter &converter,
191-
const evaluate::Expr<evaluate::SomeType> &expr,
192-
mlir::Value var, mlir::Value shapeBuffer,
193-
SymMap &symMap, StatementContext &stmtCtx);
172+
/// Somewhat similar to createSomeArrayTempValue, but the temporary buffer is
173+
/// allocated lazily (inside the loops instead of before the loops) to
174+
/// accomodate buffers with shapes that cannot be precomputed. In fact, the
175+
/// buffer need not even be hyperrectangular. The buffer may be created as an
176+
/// instance of a ragged array, which may be useful if an array's extents are
177+
/// functions of other loop indices. The ragged array structure is built with \p
178+
/// raggedHeader being the root header variable. The header is a tuple of
179+
/// `{rank, data-is-headers, [data]*, [extents]*}`, which is built recursively.
180+
/// The base header, \p raggedHeader, must be initialized to zeros.
181+
void createLazyArrayTempValue(AbstractConverter &converter,
182+
const evaluate::Expr<evaluate::SomeType> &expr,
183+
mlir::Value raggedHeader, SymMap &symMap,
184+
StatementContext &stmtCtx);
194185

195186
/// Lower an array expression to a value of type box. The expression must be a
196187
/// variable.

flang/include/flang/Optimizer/Builder/FIRBuilder.h

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -465,6 +465,8 @@ void genRecordAssignment(fir::FirOpBuilder &builder, mlir::Location loc,
465465
const fir::ExtendedValue &lhs,
466466
const fir::ExtendedValue &rhs);
467467

468+
mlir::TupleType getRaggedArrayHeaderType(fir::FirOpBuilder &builder);
469+
468470
} // namespace fir::factory
469471

470472
#endif // FORTRAN_OPTIMIZER_BUILDER_FIRBUILDER_H

flang/include/flang/Optimizer/Builder/Runtime/RTBuilder.h

Lines changed: 15 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -105,10 +105,16 @@ constexpr TypeBuilderFunc getModel<signed char>() {
105105
};
106106
}
107107
template <>
108+
constexpr TypeBuilderFunc getModel<void *>() {
109+
return [](mlir::MLIRContext *context) -> mlir::Type {
110+
return fir::LLVMPointerType::get(mlir::IntegerType::get(context, 8));
111+
};
112+
}
113+
template <>
108114
constexpr TypeBuilderFunc getModel<void **>() {
109115
return [](mlir::MLIRContext *context) -> mlir::Type {
110116
return fir::ReferenceType::get(
111-
fir::PointerType::get(mlir::IntegerType::get(context, 8)));
117+
fir::LLVMPointerType::get(mlir::IntegerType::get(context, 8)));
112118
};
113119
}
114120
template <>
@@ -125,6 +131,10 @@ constexpr TypeBuilderFunc getModel<long &>() {
125131
};
126132
}
127133
template <>
134+
constexpr TypeBuilderFunc getModel<long *>() {
135+
return getModel<long &>();
136+
}
137+
template <>
128138
constexpr TypeBuilderFunc getModel<long long>() {
129139
return [](mlir::MLIRContext *context) -> mlir::Type {
130140
return mlir::IntegerType::get(context, 8 * sizeof(std::size_t));
@@ -138,6 +148,10 @@ constexpr TypeBuilderFunc getModel<long long &>() {
138148
};
139149
}
140150
template <>
151+
constexpr TypeBuilderFunc getModel<long long *>() {
152+
return getModel<long long &>();
153+
}
154+
template <>
141155
constexpr TypeBuilderFunc getModel<unsigned long>() {
142156
return [](mlir::MLIRContext *context) -> mlir::Type {
143157
return mlir::IntegerType::get(context, 8 * sizeof(unsigned long));
Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,39 @@
1+
//===-- Ragged.h ------------------------------------------------*- C++ -*-===//
2+
//
3+
// Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4+
// See https://llvm.org/LICENSE.txt for license information.
5+
// SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6+
//
7+
//===----------------------------------------------------------------------===//
8+
9+
#ifndef FORTRAN_OPTIMIZER_BUILDER_RUNTIME_RAGGED_H
10+
#define FORTRAN_OPTIMIZER_BUILDER_RUNTIME_RAGGED_H
11+
12+
namespace mlir {
13+
class Location;
14+
class Value;
15+
class ValueRange;
16+
} // namespace mlir
17+
18+
namespace fir {
19+
class FirOpBuilder;
20+
} // namespace fir
21+
22+
namespace fir::runtime {
23+
24+
/// Generate code to instantiate a section of a ragged array. Calls the runtime
25+
/// to initialize the data buffer. \p header must be a ragged buffer header (on
26+
/// the heap) and will be initialized, if and only if the rank of \p extents is
27+
/// at least 1 and all values in the vector of extents are positive. \p extents
28+
/// must be a vector of Value of type `i64`. \p eleSize is in bytes, not bits.
29+
void genRaggedArrayAllocate(mlir::Location loc, fir::FirOpBuilder &builder,
30+
mlir::Value header, bool asHeaders,
31+
mlir::Value eleSize, mlir::ValueRange extents);
32+
33+
/// Generate a call to the runtime routine to deallocate a ragged array data
34+
/// structure on the heap.
35+
void genRaggedArrayDeallocate(mlir::Location loc, fir::FirOpBuilder &builder,
36+
mlir::Value header);
37+
38+
} // namespace fir::runtime
39+
#endif // FORTRAN_OPTIMIZER_BUILDER_RUNTIME_RAGGED_H

flang/include/flang/Runtime/ragged.h

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,24 @@
1+
//===-- Runtime/ragged.h ----------------------------------------*- C++ -*-===//
2+
//
3+
// Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4+
// See https://llvm.org/LICENSE.txt for license information.
5+
// SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6+
//
7+
//===----------------------------------------------------------------------===//
8+
9+
#ifndef FORTRAN_RUNTIME_RAGGED_H_
10+
#define FORTRAN_RUNTIME_RAGGED_H_
11+
12+
#include "flang/Runtime/entry-names.h"
13+
#include <cstdint>
14+
15+
namespace Fortran::runtime {
16+
extern "C" {
17+
// Helper for allocation of ragged array buffer blocks.
18+
void *RTNAME(RaggedArrayAllocate)(
19+
void *, bool, std::int64_t, std::int64_t, std::int64_t *);
20+
// Helper for deallocation of ragged array buffers.
21+
void RTNAME(RaggedArrayDeallocate)(void *);
22+
} // extern "C"
23+
} // namespace Fortran::runtime
24+
#endif // FORTRAN_RUNTIME_RAGGED_H_

flang/lib/Lower/Bridge.cpp

Lines changed: 32 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@
3232
#include "flang/Optimizer/Builder/Character.h"
3333
#include "flang/Optimizer/Builder/FIRBuilder.h"
3434
#include "flang/Optimizer/Builder/Runtime/Character.h"
35+
#include "flang/Optimizer/Builder/Runtime/Ragged.h"
3536
#include "flang/Optimizer/Dialect/FIRAttr.h"
3637
#include "flang/Optimizer/Dialect/FIRDialect.h"
3738
#include "flang/Optimizer/Dialect/FIROps.h"
@@ -1263,8 +1264,9 @@ class FirConverter : public Fortran::lower::AbstractConverter {
12631264
forceControlVariableBinding(ctrlVar, lp.getInductionVar());
12641265
loops.push_back(lp);
12651266
}
1266-
if (outermost)
1267-
explicitIterSpace.setOuterLoop(loops[0]);
1267+
if (outermost)
1268+
explicitIterSpace.setOuterLoop(loops[0]);
1269+
explicitIterSpace.appendLoops(loops);
12681270
if (const auto &mask =
12691271
std::get<std::optional<Fortran::parser::ScalarLogicalExpr>>(
12701272
header.t);
@@ -2749,23 +2751,36 @@ class FirConverter : public Fortran::lower::AbstractConverter {
27492751
// with sequences of i1. That is, an array of i1 will be truncated in size
27502752
// and be too small. For example, a buffer of type fir.array<7xi1> will have
27512753
// 0 size.
2752-
auto ty = fir::HeapType::get(builder->getIntegerType(8));
2754+
auto i64Ty = builder->getIntegerType(64);
2755+
auto ty = fir::factory::getRaggedArrayHeaderType(*builder);
2756+
auto buffTy = ty.getType(1);
2757+
auto shTy = ty.getType(2);
27532758
auto loc = toLocation();
2754-
auto var = builder->createTemporary(loc, ty);
2755-
auto nil = builder->createNullConstant(loc, ty);
2756-
builder->create<fir::StoreOp>(loc, nil, var);
2757-
auto shTy = fir::HeapType::get(builder->getIndexType());
2758-
auto shape = builder->createTemporary(loc, shTy);
2759-
auto nilSh = builder->createNullConstant(loc, shTy);
2760-
builder->create<fir::StoreOp>(loc, nilSh, shape);
2761-
implicitIterSpace.addMaskVariable(exp, var, shape);
2759+
auto hdr = builder->createTemporary(loc, ty);
2760+
// FIXME: Is there a way to create a `zeroinitializer` in LLVM-IR dialect?
2761+
// For now, explicitly set lazy ragged header to all zeros.
2762+
// auto nilTup = builder->createNullConstant(loc, ty);
2763+
// builder->create<fir::StoreOp>(loc, nilTup, hdr);
2764+
auto i32Ty = builder->getIntegerType(32);
2765+
auto zero = builder->createIntegerConstant(loc, i32Ty, 0);
2766+
auto zero64 = builder->createIntegerConstant(loc, i64Ty, 0);
2767+
mlir::Value flags = builder->create<fir::CoordinateOp>(
2768+
loc, builder->getRefType(i64Ty), hdr, zero);
2769+
builder->create<fir::StoreOp>(loc, zero64, flags);
2770+
auto one = builder->createIntegerConstant(loc, i32Ty, 1);
2771+
auto nullPtr1 = builder->createNullConstant(loc, buffTy);
2772+
mlir::Value var = builder->create<fir::CoordinateOp>(
2773+
loc, builder->getRefType(buffTy), hdr, one);
2774+
builder->create<fir::StoreOp>(loc, nullPtr1, var);
2775+
auto two = builder->createIntegerConstant(loc, i32Ty, 2);
2776+
auto nullPtr2 = builder->createNullConstant(loc, shTy);
2777+
mlir::Value shape = builder->create<fir::CoordinateOp>(
2778+
loc, builder->getRefType(shTy), hdr, two);
2779+
builder->create<fir::StoreOp>(loc, nullPtr2, shape);
2780+
implicitIterSpace.addMaskVariable(exp, var, shape, hdr);
27622781
explicitIterSpace.outermostContext().attachCleanup(
2763-
[builder = this->builder, loc, var]() {
2764-
auto load = builder->create<fir::LoadOp>(loc, var);
2765-
auto cmp = builder->genIsNotNull(loc, load);
2766-
builder->genIfThen(loc, cmp)
2767-
.genThen([&]() { builder->create<fir::FreeMemOp>(loc, load); })
2768-
.end();
2782+
[builder = this->builder, hdr, loc]() {
2783+
fir::runtime::genRaggedArrayDeallocate(loc, *builder, hdr);
27692784
});
27702785
}
27712786

0 commit comments

Comments
 (0)