Skip to content

Commit 7184230

Browse files
authored
Merge pull request #1068 from Huawei-PTLab/lowering-stubs
[flang] Add lowering stubs for OpenMP/OpenACC declarative constructs
2 parents 06af207 + 780d3fc commit 7184230

File tree

13 files changed

+152
-6
lines changed

13 files changed

+152
-6
lines changed

flang/include/flang/Lower/OpenACC.h

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@
1616
namespace Fortran {
1717
namespace parser {
1818
struct OpenACCConstruct;
19+
struct OpenACCDeclarativeConstruct;
1920
} // namespace parser
2021

2122
namespace lower {
@@ -28,6 +29,9 @@ struct Evaluation;
2829

2930
void genOpenACCConstruct(AbstractConverter &, pft::Evaluation &,
3031
const parser::OpenACCConstruct &);
32+
void genOpenACCDeclarativeConstruct(
33+
AbstractConverter &, pft::Evaluation &,
34+
const parser::OpenACCDeclarativeConstruct &);
3135

3236
} // namespace lower
3337
} // namespace Fortran

flang/include/flang/Lower/OpenMP.h

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@
1818
namespace Fortran {
1919
namespace parser {
2020
struct OpenMPConstruct;
21+
struct OpenMPDeclarativeConstruct;
2122
struct OmpEndLoopDirective;
2223
struct OmpClauseList;
2324
} // namespace parser
@@ -32,6 +33,8 @@ struct Evaluation;
3233

3334
void genOpenMPConstruct(AbstractConverter &, pft::Evaluation &,
3435
const parser::OpenMPConstruct &);
36+
void genOpenMPDeclarativeConstruct(AbstractConverter &, pft::Evaluation &,
37+
const parser::OpenMPDeclarativeConstruct &);
3538

3639
int64_t getCollapseValue(const Fortran::parser::OmpClauseList &clauseList);
3740

flang/include/flang/Lower/PFTBuilder.h

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -134,7 +134,9 @@ using Constructs =
134134

135135
using Directives =
136136
std::tuple<parser::CompilerDirective, parser::OpenACCConstruct,
137-
parser::OpenMPConstruct, parser::OmpEndLoopDirective>;
137+
parser::OpenMPConstruct, parser::OmpEndLoopDirective,
138+
parser::OpenMPDeclarativeConstruct,
139+
parser::OpenACCDeclarativeConstruct>;
138140

139141
template <typename A>
140142
static constexpr bool isActionStmt{common::HasMember<A, ActionStmts>};

flang/lib/Lower/Bridge.cpp

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1363,6 +1363,14 @@ class FirConverter : public Fortran::lower::AbstractConverter {
13631363
builder->restoreInsertionPoint(insertPt);
13641364
}
13651365

1366+
void genFIR(const Fortran::parser::OpenACCDeclarativeConstruct &accDecl) {
1367+
auto insertPt = builder->saveInsertionPoint();
1368+
genOpenACCDeclarativeConstruct(*this, getEval(), accDecl);
1369+
for (auto &e : getEval().getNestedEvaluations())
1370+
genFIR(e);
1371+
builder->restoreInsertionPoint(insertPt);
1372+
}
1373+
13661374
void genFIR(const Fortran::parser::OpenMPConstruct &omp) {
13671375
auto insertPt = builder->saveInsertionPoint();
13681376
localSymbols.pushScope();
@@ -1395,6 +1403,14 @@ class FirConverter : public Fortran::lower::AbstractConverter {
13951403
builder->restoreInsertionPoint(insertPt);
13961404
}
13971405

1406+
void genFIR(const Fortran::parser::OpenMPDeclarativeConstruct &ompDecl) {
1407+
auto insertPt = builder->saveInsertionPoint();
1408+
genOpenMPDeclarativeConstruct(*this, getEval(), ompDecl);
1409+
for (auto &e : getEval().getNestedEvaluations())
1410+
genFIR(e);
1411+
builder->restoreInsertionPoint(insertPt);
1412+
}
1413+
13981414
/// Generate FIR for a SELECT CASE statement.
13991415
/// The type may be CHARACTER, INTEGER, or LOGICAL.
14001416
void genFIR(const Fortran::parser::SelectCaseStmt &stmt) {

flang/lib/Lower/OpenACC.cpp

Lines changed: 21 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1022,11 +1022,6 @@ void Fortran::lower::genOpenACCConstruct(
10221022
&standaloneConstruct) {
10231023
genACC(converter, eval, standaloneConstruct);
10241024
},
1025-
[&](const Fortran::parser::OpenACCRoutineConstruct
1026-
&routineConstruct) {
1027-
TODO(converter.genLocation(),
1028-
"OpenACC Routine construct not lowered yet!");
1029-
},
10301025
[&](const Fortran::parser::OpenACCCacheConstruct &cacheConstruct) {
10311026
TODO(converter.genLocation(),
10321027
"OpenACC Cache construct not lowered yet!");
@@ -1041,3 +1036,24 @@ void Fortran::lower::genOpenACCConstruct(
10411036
},
10421037
accConstruct.u);
10431038
}
1039+
1040+
void Fortran::lower::genOpenACCDeclarativeConstruct(
1041+
Fortran::lower::AbstractConverter &converter,
1042+
Fortran::lower::pft::Evaluation &eval,
1043+
const Fortran::parser::OpenACCDeclarativeConstruct &accDeclConstruct) {
1044+
1045+
std::visit(
1046+
common::visitors{
1047+
[&](const Fortran::parser::OpenACCStandaloneDeclarativeConstruct
1048+
&standaloneDeclarativeConstruct) {
1049+
TODO(converter.genLocation(),
1050+
"OpenACC Standalone Declarative construct not lowered yet!");
1051+
},
1052+
[&](const Fortran::parser::OpenACCRoutineConstruct
1053+
&routineConstruct) {
1054+
TODO(converter.genLocation(),
1055+
"OpenACC Routine construct not lowered yet!");
1056+
},
1057+
},
1058+
accDeclConstruct.u);
1059+
}

flang/lib/Lower/OpenMP.cpp

Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -685,3 +685,35 @@ void Fortran::lower::genOpenMPConstruct(
685685
},
686686
ompConstruct.u);
687687
}
688+
689+
void Fortran::lower::genOpenMPDeclarativeConstruct(
690+
Fortran::lower::AbstractConverter &converter,
691+
Fortran::lower::pft::Evaluation &eval,
692+
const Fortran::parser::OpenMPDeclarativeConstruct &ompDeclConstruct) {
693+
694+
std::visit(
695+
common::visitors{
696+
[&](const Fortran::parser::OpenMPDeclarativeAllocate
697+
&declarativeAllocate) {
698+
TODO(converter.getCurrentLocation(), "OpenMPDeclarativeAllocate");
699+
},
700+
[&](const Fortran::parser::OpenMPDeclareReductionConstruct
701+
&declareReductionConstruct) {
702+
TODO(converter.getCurrentLocation(),
703+
"OpenMPDeclareReductionConstruct");
704+
},
705+
[&](const Fortran::parser::OpenMPDeclareSimdConstruct
706+
&declareSimdConstruct) {
707+
TODO(converter.getCurrentLocation(), "OpenMPDeclareSimdConstruct");
708+
},
709+
[&](const Fortran::parser::OpenMPDeclareTargetConstruct
710+
&declareTargetConstruct) {
711+
TODO(converter.getCurrentLocation(),
712+
"OpenMPDeclareTargetConstruct");
713+
},
714+
[&](const Fortran::parser::OpenMPThreadprivate &threadprivate) {
715+
TODO(converter.getCurrentLocation(), "OpenMPThreadprivate");
716+
},
717+
},
718+
ompDeclConstruct.u);
719+
}
Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
! This test checks lowering of OpenACC declare Directive.
2+
! XFAIL: *
3+
! RUN: %bbc -fopenacc -emit-fir %s -o - | FileCheck %s
4+
5+
program main
6+
real, dimension(10) :: aa, bb
7+
8+
!$acc declare present(aa, bb)
9+
end
Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
! This test checks lowering of OpenACC routine Directive.
2+
! XFAIL: *
3+
! RUN: %bbc -fopenacc -emit-fir %s -o - | FileCheck %s
4+
5+
program main
6+
!$acc routine(sub) seq
7+
contains
8+
subroutine sub(a)
9+
real :: a(:)
10+
end
11+
end
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
! This test checks lowering of OpenMP allocate Directive.
2+
! XFAIL: *
3+
! RUN: %bbc -fopenmp -emit-fir %s -o - | \
4+
! RUN: FileCheck %s --check-prefix=FIRDialect
5+
6+
program main
7+
integer :: x, y
8+
9+
!$omp allocate(x, y)
10+
end
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
! This test checks lowering of OpenMP declare reduction Directive.
2+
! XFAIL: *
3+
! RUN: %bbc -fopenmp -emit-fir %s -o - | \
4+
! RUN: FileCheck %s --check-prefix=FIRDialect
5+
6+
subroutine declare_red()
7+
integer :: my_var
8+
!$omp declare reduction (my_red : integer : omp_out = omp_in) initializer (omp_priv = 0)
9+
my_var = 0
10+
end subroutine declare_red

0 commit comments

Comments
 (0)