Skip to content

Commit 8f2a892

Browse files
committed
[flang][openacc] Lower loop with collapse clause
1 parent 46839d2 commit 8f2a892

File tree

5 files changed

+142
-10
lines changed

5 files changed

+142
-10
lines changed

flang/include/flang/Optimizer/Dialect/FIRDialect.h

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -43,6 +43,7 @@ inline void registerFIR() {
4343
[[maybe_unused]] static bool init_once = [] {
4444
mlir::registerDialect<mlir::AffineDialect>();
4545
mlir::registerDialect<mlir::LLVM::LLVMDialect>();
46+
mlir::registerDialect<mlir::acc::OpenACCDialect>();
4647
mlir::registerDialect<mlir::omp::OpenMPDialect>();
4748
mlir::registerDialect<mlir::scf::SCFDialect>();
4849
mlir::registerDialect<mlir::StandardOpsDialect>();

flang/lib/Lower/Bridge.cpp

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@
2121
#include "flang/Lower/FIRBuilder.h"
2222
#include "flang/Lower/IO.h"
2323
#include "flang/Lower/Mangler.h"
24+
#include "flang/Lower/OpenACC.h"
2425
#include "flang/Lower/OpenMP.h"
2526
#include "flang/Lower/PFTBuilder.h"
2627
#include "flang/Lower/Runtime.h"
@@ -1057,7 +1058,13 @@ class FirConverter : public Fortran::lower::AbstractConverter {
10571058
mlir::emitWarning(toLocation(), "ignoring all compiler directives");
10581059
}
10591060

1060-
void genFIR(const Fortran::parser::OpenACCConstruct &) { TODO(); }
1061+
void genFIR(const Fortran::parser::OpenACCConstruct &acc) {
1062+
auto insertPt = builder->saveInsertionPoint();
1063+
genOpenACCConstruct(*this, getEval(), acc);
1064+
for (auto &e : getEval().getNestedEvaluations())
1065+
genFIR(e);
1066+
builder->restoreInsertionPoint(insertPt);
1067+
}
10611068

10621069
void genFIR(const Fortran::parser::OpenMPConstruct &omp) {
10631070
genOpenMPConstruct(*this, getEval(), omp);

flang/lib/Lower/OpenACC.cpp

Lines changed: 69 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -15,24 +15,85 @@
1515
#include "flang/Lower/FIRBuilder.h"
1616
#include "flang/Lower/PFTBuilder.h"
1717
#include "flang/Parser/parse-tree.h"
18+
#include "flang/Semantics/tools.h"
19+
#include "mlir/Dialect/OpenACC/OpenACC.h"
1820
#include "llvm/Frontend/OpenACC/ACC.h.inc"
1921

2022
#define TODO() llvm_unreachable("not yet implemented")
2123

24+
static void genACC(Fortran::lower::AbstractConverter &absConv,
25+
Fortran::lower::pft::Evaluation &eval,
26+
const Fortran::parser::OpenACCLoopConstruct &loopConstruct) {
27+
28+
const auto &beginLoopDirective =
29+
std::get<Fortran::parser::AccBeginLoopDirective>(loopConstruct.t);
30+
const auto &loopDirective =
31+
std::get<Fortran::parser::AccLoopDirective>(beginLoopDirective.t);
32+
33+
if (loopDirective.v == llvm::acc::ACCD_loop) {
34+
auto &firOpBuilder = absConv.getFirOpBuilder();
35+
auto currentLocation = absConv.getCurrentLocation();
36+
llvm::ArrayRef<mlir::Type> argTy;
37+
mlir::ValueRange range;
38+
// Temporarly set to default 0 as operands are not generated yet.
39+
llvm::SmallVector<int32_t, 2> operandSegmentSizes(/*Size=*/2,
40+
/*Value=*/0);
41+
auto loopOp =
42+
firOpBuilder.create<mlir::acc::LoopOp>(currentLocation, argTy, range);
43+
loopOp.setAttr(mlir::acc::LoopOp::getOperandSegmentSizeAttr(),
44+
firOpBuilder.getI32VectorAttr(operandSegmentSizes));
45+
firOpBuilder.createBlock(&loopOp.getRegion());
46+
auto &block = loopOp.getRegion().back();
47+
firOpBuilder.setInsertionPointToStart(&block);
48+
// ensure the block is well-formed.
49+
firOpBuilder.create<mlir::acc::YieldOp>(currentLocation);
50+
51+
// Add attribute extracted from clauses.
52+
const auto &accClauseList =
53+
std::get<Fortran::parser::AccClauseList>(beginLoopDirective.t);
54+
55+
//
56+
for (const auto &clause : accClauseList.v) {
57+
if (const auto *collapseClause =
58+
std::get_if<Fortran::parser::AccClause::Collapse>(&clause.u)) {
59+
60+
const auto *expr = Fortran::semantics::GetExpr(collapseClause->v);
61+
const auto collapseValue = Fortran::evaluate::ToInt64(*expr);
62+
if (collapseValue.has_value()) {
63+
loopOp.setAttr(mlir::acc::LoopOp::getCollapseAttrName(),
64+
firOpBuilder.getI64IntegerAttr(collapseValue.value()));
65+
}
66+
} else if (const auto *seqClause =
67+
std::get_if<Fortran::parser::AccClause::Seq>(&clause.u)) {
68+
} else if (const auto *gangClause =
69+
std::get_if<Fortran::parser::AccClause::Gang>(&clause.u)) {
70+
} else if (const auto *vectorClause =
71+
std::get_if<Fortran::parser::AccClause::Vector>(&clause.u)) {
72+
} else if (const auto *workerClause =
73+
std::get_if<Fortran::parser::AccClause::Worker>(&clause.u)) {
74+
}
75+
76+
77+
}
78+
79+
// Place the insertion point to the start of the first block.
80+
firOpBuilder.setInsertionPointToStart(&block);
81+
}
82+
}
83+
2284
void Fortran::lower::genOpenACCConstruct(
23-
Fortran::lower::AbstractConverter &absConv,
85+
Fortran::lower::AbstractConverter &converter,
2486
Fortran::lower::pft::Evaluation &eval,
25-
const Fortran::parser::OpenACCConstruct &accConstruct) {
26-
87+
const Fortran::parser::OpenACCConstruct &acc) {
2788
std::visit(
28-
common::visitors{
89+
Fortran::common::visitors{
2990
[&](const Fortran::parser::OpenACCBlockConstruct &blockConstruct) {
3091
TODO();
3192
},
3293
[&](const Fortran::parser::OpenACCCombinedConstruct
3394
&combinedConstruct) { TODO(); },
3495
[&](const Fortran::parser::OpenACCLoopConstruct &loopConstruct) {
35-
TODO();
96+
genACC(converter, eval, loopConstruct);
3697
},
3798
[&](const Fortran::parser::OpenACCStandaloneConstruct
3899
&standaloneConstruct) { TODO(); },
@@ -44,9 +105,8 @@ void Fortran::lower::genOpenACCConstruct(
44105
[&](const Fortran::parser::OpenACCWaitConstruct &waitConstruct) {
45106
TODO();
46107
},
47-
[&](const Fortran::parser::OpenACCAtomicConstruct &atomicConstruct) {
48-
TODO();
49-
},
108+
[&](const Fortran::parser::OpenACCAtomicConstruct
109+
&atomicConstruct) { TODO(); },
50110
},
51-
accConstruct.u);
111+
acc.u);
52112
}

flang/test/Lower/OpenACC/acc-loop.f90

Lines changed: 54 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,54 @@
1+
! This test checks lowering of OpenACC loop directive.
2+
3+
! RUN: bbc -fopenacc -emit-fir %s -o - | FileCheck %s
4+
5+
program acc_loop
6+
7+
integer :: i, j
8+
integer, parameter :: n = 10
9+
real, dimension(n) :: a, b
10+
real, dimension(n, n) :: c, d
11+
12+
13+
!$acc loop
14+
DO i = 1, n
15+
a(i) = b(i)
16+
END DO
17+
18+
!CHECK: acc.loop {
19+
!CHECK: fir.do_loop
20+
!CHECK: acc.yield
21+
!CHECK-NEXT: }
22+
23+
!$acc loop collapse(2)
24+
DO i = 1, n
25+
DO j = 1, n
26+
c(i, j) = d(i, j)
27+
END DO
28+
END DO
29+
30+
!CHECK: acc.loop {
31+
!CHECK: fir.do_loop
32+
!CHECK: fir.do_loop
33+
!CHECK: acc.yield
34+
!CHECK-NEXT: } attributes {collapse = 2 : i64}
35+
36+
!$acc loop
37+
DO i = 1, n
38+
!$acc loop
39+
DO j = 1, n
40+
c(i, j) = d(i, j)
41+
END DO
42+
END DO
43+
44+
!CHECK: acc.loop {
45+
!CHECK: fir.do_loop
46+
!CHECK: acc.loop {
47+
!CHECK: fir.do_loop
48+
!CHECK: acc.yield
49+
!CHECK-NEXT: }
50+
!CHECK: acc.yield
51+
!CHECK-NEXT: }
52+
53+
end program
54+

flang/tools/bbc/bbc.cpp

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -116,6 +116,10 @@ static llvm::cl::opt<bool> enableOpenMP("fopenmp",
116116
llvm::cl::desc("enable openmp"),
117117
llvm::cl::init(false));
118118

119+
static llvm::cl::opt<bool> enableOpenACC("fopenacc",
120+
llvm::cl::desc("enable openacc"),
121+
llvm::cl::init(false));
122+
119123
static llvm::cl::opt<bool> dumpModuleOnFailure("dump-module-on-failure",
120124
llvm::cl::init(false));
121125

@@ -153,6 +157,12 @@ static mlir::LogicalResult convertFortranSourceToMLIR(
153157
options.predefinitions.emplace_back("_OPENMP", "201511");
154158
}
155159

160+
// enable parsing of OpenACC
161+
if (enableOpenACC) {
162+
options.features.Enable(Fortran::common::LanguageFeature::OpenACC);
163+
options.predefinitions.emplace_back("_OPENACC", "201911");
164+
}
165+
156166
// prep for prescan and parse
157167
options.searchDirectories = includeDirs;
158168
Fortran::parser::Parsing parsing{semanticsContext.allSources()};

0 commit comments

Comments
 (0)