@@ -107,7 +107,39 @@ static void genObjectList(const Fortran::parser::OmpObjectList &objectList,
107107 ompObject.u );
108108 }
109109}
110+ static void handleAllocateClause (
111+ Fortran::lower::AbstractConverter &converter,
112+ const Fortran::parser::OmpAllocateClause &ompAllocateClause,
113+ SmallVector<Value> &allocatorOperands,
114+ SmallVector<Value> &allocateOperands) {
115+ auto &firOpBuilder = converter.getFirOpBuilder ();
116+ auto currentLocation = converter.getCurrentLocation ();
117+ Fortran::lower::StatementContext stmtCtx;
110118
119+ mlir::Value allocatorOperand;
120+ const Fortran::parser::OmpObjectList &ompObjectList =
121+ std::get<Fortran::parser::OmpObjectList>(ompAllocateClause.t );
122+ const auto &allocatorValue =
123+ std::get<std::optional<Fortran::parser::OmpAllocateClause::Allocator>>(
124+ ompAllocateClause.t );
125+ // Check if allocate clause has allocator specified. If so, add it
126+ // to list of allocators, otherwise, add default allocator to
127+ // list of allocators.
128+
129+ if (allocatorValue) {
130+ allocatorOperand = fir::getBase (converter.genExprValue (
131+ *Fortran::semantics::GetExpr (allocatorValue->v ), stmtCtx));
132+ allocatorOperands.insert (allocatorOperands.end (), ompObjectList.v .size (),
133+ allocatorOperand);
134+ } else {
135+ allocatorOperand = firOpBuilder.createIntegerConstant (
136+ currentLocation, firOpBuilder.getI32Type (), 1 );
137+ allocatorOperands.insert (allocatorOperands.end (), ompObjectList.v .size (),
138+ allocatorOperand);
139+ }
140+
141+ genObjectList (ompObjectList, converter, allocateOperands);
142+ }
111143// / Create empty blocks for the current region.
112144// / These blocks replace blocks parented to an enclosing region.
113145void createEmptyRegionBlocks (
@@ -306,9 +338,9 @@ static void createParallelOp(Fortran::lower::AbstractConverter &converter,
306338 Fortran::lower::StatementContext stmtCtx;
307339 llvm::ArrayRef<mlir::Type> argTy;
308340 mlir::Value ifClauseOperand, numThreadsClauseOperand;
309- llvm:: SmallVector<Value, 4 > privateClauseOperands, firstprivateClauseOperands,
310- sharedClauseOperands, copyinClauseOperands, allocatorOperands,
311- allocateOperands;
341+ SmallVector<Value, 4 > privateClauseOperands, firstprivateClauseOperands,
342+ sharedClauseOperands, copyinClauseOperands;
343+ SmallVector<Value> allocatorOperands, allocateOperands;
312344 Attribute defaultClauseOperand, procBindClauseOperand;
313345 const auto &opClauseList =
314346 std::get<Fortran::parser::OmpClauseList>(directive.t );
@@ -334,29 +366,8 @@ static void createParallelOp(Fortran::lower::AbstractConverter &converter,
334366 } else if (const auto &allocateClause =
335367 std::get_if<Fortran::parser::OmpClause::Allocate>(
336368 &clause.u )) {
337- mlir::Value allocatorOperand;
338- const Fortran::parser::OmpAllocateClause &ompAllocateClause =
339- allocateClause->v ;
340- const Fortran::parser::OmpObjectList &ompObjectList =
341- std::get<Fortran::parser::OmpObjectList>(ompAllocateClause.t );
342- // Check if allocate clause has allocator specified. If so, add it
343- // to list of allocators, otherwise, add default allocator to
344- // list of allocators.
345- const auto &allocatorValue = std::get<
346- std::optional<Fortran::parser::OmpAllocateClause::Allocator>>(
347- ompAllocateClause.t );
348- if (allocatorValue) {
349- allocatorOperand = fir::getBase (converter.genExprValue (
350- *Fortran::semantics::GetExpr (allocatorValue->v ), stmtCtx));
351- allocatorOperands.insert (allocatorOperands.end (),
352- ompObjectList.v .size (), allocatorOperand);
353- } else {
354- allocatorOperand = firOpBuilder.createIntegerConstant (
355- currentLocation, firOpBuilder.getI32Type (), 1 );
356- allocatorOperands.insert (allocatorOperands.end (),
357- ompObjectList.v .size (), allocatorOperand);
358- }
359- genObjectList (ompObjectList, converter, allocateOperands);
369+ handleAllocateClause (converter, allocateClause->v , allocatorOperands,
370+ allocateOperands);
360371 }
361372 }
362373 // Create and insert the operation.
@@ -746,6 +757,65 @@ genOMP(Fortran::lower::AbstractConverter &converter,
746757 createBodyOfOp<omp::CriticalOp>(criticalOp, converter, currentLocation, eval);
747758}
748759
760+ void Fortran::lower::genOpenMPSectionsBlock (
761+ Fortran::lower::AbstractConverter &converter,
762+ Fortran::lower::pft::Evaluation &eval) {
763+ auto &firOpBuilder = converter.getFirOpBuilder ();
764+ auto currentLocation = converter.getCurrentLocation ();
765+ mlir::omp::SectionOp sectionOp =
766+ firOpBuilder.create <mlir::omp::SectionOp>(currentLocation);
767+ createBodyOfOp<omp::SectionOp>(sectionOp, converter, currentLocation, eval);
768+ }
769+
770+ // TODO: Add support for reduction and lastprivate
771+ static void
772+ genOMP (Fortran::lower::AbstractConverter &converter,
773+ Fortran::lower::pft::Evaluation &eval,
774+ const Fortran::parser::OpenMPSectionsConstruct §ionsConstruct) {
775+ auto &firOpBuilder = converter.getFirOpBuilder ();
776+ auto currentLocation = converter.getCurrentLocation ();
777+ SmallVector<Value> privateClauseOperands, firstPrivateClauseOperands,
778+ lastPrivateClauseOperands, reductionVars, allocateOperands,
779+ allocatorOperands;
780+ mlir::UnitAttr noWaitClauseOperand;
781+ const auto §ionsClauseList = std::get<Fortran::parser::OmpClauseList>(
782+ std::get<Fortran::parser::OmpBeginSectionsDirective>(
783+ sectionsConstruct.t )
784+ .t );
785+ for (const auto &clause : sectionsClauseList.v ) {
786+ if (std::get_if<Fortran::parser::OmpClause::Lastprivate>(&clause.u )) {
787+ TODO (currentLocation, " OMPC_LastPrivate" );
788+ }
789+ if (std::get_if<Fortran::parser::OmpClause::Reduction>(&clause.u )) {
790+ TODO (currentLocation, " OMPC_Reduction" );
791+ }
792+ if (const auto &allocateClause =
793+ std::get_if<Fortran::parser::OmpClause::Allocate>(&clause.u )) {
794+ handleAllocateClause (converter, allocateClause->v , allocatorOperands,
795+ allocateOperands);
796+ }
797+ }
798+ const auto &endSectionsClauseList =
799+ std::get<Fortran::parser::OmpEndSectionsDirective>(
800+ sectionsConstruct.t );
801+ const auto &clauseList =
802+ std::get<Fortran::parser::OmpClauseList>(endSectionsClauseList.t );
803+ for (const auto &clause : clauseList.v ) {
804+ if (std::get_if<Fortran::parser::OmpClause::Nowait>(&clause.u )) {
805+ noWaitClauseOperand = firOpBuilder.getUnitAttr ();
806+ }
807+ }
808+
809+ mlir::omp::SectionsOp sectionsOp =
810+ firOpBuilder.create <mlir::omp::SectionsOp>(
811+ currentLocation, privateClauseOperands, firstPrivateClauseOperands,
812+ lastPrivateClauseOperands, reductionVars, nullptr ,
813+ allocateOperands, allocatorOperands, noWaitClauseOperand);
814+
815+ createBodyOfOp<omp::SectionsOp>(sectionsOp, converter, currentLocation,
816+ eval, §ionsClauseList);
817+ }
818+
749819void Fortran::lower::genOpenMPConstruct (
750820 Fortran::lower::AbstractConverter &converter,
751821 Fortran::lower::pft::Evaluation &eval,
@@ -759,7 +829,7 @@ void Fortran::lower::genOpenMPConstruct(
759829 },
760830 [&](const Fortran::parser::OpenMPSectionsConstruct
761831 §ionsConstruct) {
762- TODO (converter. getCurrentLocation (), " OpenMPSectionsConstruct " );
832+ genOMP (converter, eval, sectionsConstruct );
763833 },
764834 [&](const Fortran::parser::OpenMPLoopConstruct &loopConstruct) {
765835 genOMP (converter, eval, loopConstruct);
0 commit comments