Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
31 changes: 18 additions & 13 deletions flang/lib/Lower/OpenMP.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -137,7 +137,7 @@ void createEmptyRegionBlocks(
// }
}
}
if (eval.hasNestedEvaluations())
if (!eval.isDirective() && eval.hasNestedEvaluations())
createEmptyRegionBlocks(firOpBuilder, eval.getNestedEvaluations());
}
}
Expand All @@ -161,11 +161,12 @@ static mlir::Type getLoopVarType(Fortran::lower::AbstractConverter &converter,
}

template <typename Op>
static void createBodyOfOp(
Op &op, Fortran::lower::AbstractConverter &converter, mlir::Location &loc,
Fortran::lower::pft::Evaluation &eval,
const Fortran::parser::OmpClauseList *clauses = nullptr,
const SmallVector<const Fortran::semantics::Symbol *> &args = {}) {
static void
createBodyOfOp(Op &op, Fortran::lower::AbstractConverter &converter,
mlir::Location &loc, Fortran::lower::pft::Evaluation &eval,
const Fortran::parser::OmpClauseList *clauses = nullptr,
const SmallVector<const Fortran::semantics::Symbol *> &args = {},
bool outerCombined = false) {
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
// If an argument for the region is provided then create the block with that
// argument. Also update the symbol's address with the mlir argument value.
Expand Down Expand Up @@ -205,21 +206,28 @@ static void createBodyOfOp(
// the end of the block works for both.
mlir::Block &block = op.getRegion().back();
firOpBuilder.setInsertionPointToEnd(&block);
if (eval.lowerAsUnstructured())

// If it is an unstructured region and is not the outer region of a combined
// construct, create empty blocks for all evaluations.
if (eval.lowerAsUnstructured() && !outerCombined)
createEmptyRegionBlocks(firOpBuilder, eval.getNestedEvaluations());
// Ensure the block is well-formed by inserting terminators.

// Insert the terminator.
if constexpr (std::is_same_v<Op, omp::WsLoopOp>) {
mlir::ValueRange results;
firOpBuilder.create<mlir::omp::YieldOp>(loc, results);
} else {
firOpBuilder.create<mlir::omp::TerminatorOp>(loc);
}

// Reset the insert point to before the terminator.
if (storeOp)
firOpBuilder.setInsertionPointAfter(storeOp);
else
firOpBuilder.setInsertionPointToStart(&block);
if (clauses)

// Handle privatization. Do not privatize if this is the outer operation.
if (clauses && !outerCombined)
privatizeVars(converter, *clauses);
}

Expand Down Expand Up @@ -403,11 +411,8 @@ static void createParallelOp(Fortran::lower::AbstractConverter &converter,
}
}

// Avoid multiple privatization: If Parallel is part of a combined construct
// then privatization will be performed later when the other part of the
// combined construct is processed.
createBodyOfOp<omp::ParallelOp>(parallelOp, converter, currentLocation, eval,
isCombined ? nullptr : &opClauseList);
&opClauseList, {}, isCombined);
}

static void
Expand Down
173 changes: 173 additions & 0 deletions flang/test/Lower/OpenMP/omp-unstructured.f90
Original file line number Diff line number Diff line change
Expand Up @@ -143,10 +143,183 @@ subroutine ss4(n) ! CYCLE in OpenMP wsloop constructs
!$omp end parallel
end

! CHECK-LABEL: func @_QPss5() {
! CHECK: omp.parallel {
! CHECK: omp.wsloop {{.*}} {
! CHECK: br ^[[BB1:.*]]
! CHECK: ^[[BB1]]:
! CHECK: cond_br %13, ^[[BB2:.*]], ^[[BB4:.*]]
! CHECK: ^[[BB2]]:
! CHECK: cond_br %16, ^[[BB4]], ^[[BB3:.*]]
! CHECK: ^[[BB3]]:
! CHECK: br ^[[BB1]]
! CHECK: ^[[BB4]]:
! CHECK: omp.yield
! CHECK: }
! CHECK: omp.terminator
! CHECK: }
subroutine ss5() ! EXIT inside OpenMP wsloop (inside parallel)
integer :: x
!$omp parallel private(x)
!$omp do
do j = 1, 3
x = j * i
do k = 1, 3
if (k .eq. n) exit
x = k
x = x + k
enddo
x = j - 222
enddo
!$omp end do
!$omp end parallel
end

! CHECK-LABEL: func @_QPss6() {
! CHECK: omp.parallel {
! CHECK: br ^[[BB1_OUTER:.*]]
! CHECK: ^[[BB1_OUTER]]:
! CHECK: cond_br %{{.*}}, ^[[BB2_OUTER:.*]], ^[[BB3_OUTER:.*]]
! CHECK: ^[[BB2_OUTER]]:
! CHECK: omp.wsloop {{.*}} {
! CHECK: br ^[[BB1:.*]]
! CHECK: ^[[BB1]]:
! CHECK: cond_br %{{.*}}, ^[[BB2:.*]], ^[[BB4:.*]]
! CHECK: ^[[BB2]]:
! CHECK: cond_br %{{.*}}, ^[[BB4]], ^[[BB3:.*]]
! CHECK: ^[[BB3]]:
! CHECK: br ^[[BB1]]
! CHECK: ^[[BB4]]:
! CHECK: omp.yield
! CHECK: }
! CHECK: br ^[[BB1_OUTER]]
! CHECK: ^[[BB3_OUTER]]:
! CHECK: omp.terminator
! CHECK: }
subroutine ss6() ! EXIT inside OpenMP wsloop in a do loop (inside parallel)
integer :: x
!$omp parallel private(x)
do i = 1, 3
!$omp do
do j = 1, 3
x = j * i
do k = 1, 3
if (k .eq. n) exit
x = k
x = x + k
enddo
x = j - 222
enddo
!$omp end do
enddo
!$omp end parallel
end

! CHECK-LABEL: func @_QPss7() {
! CHECK: br ^[[BB1_OUTER:.*]]
! CHECK: ^[[BB1_OUTER]]:
! CHECK: cond_br %{{.*}}, ^[[BB2_OUTER:.*]], ^[[BB3_OUTER:.*]]
! CHECK-NEXT: ^[[BB2_OUTER:.*]]:
! CHECK: omp.parallel {
! CHECK: omp.wsloop {{.*}} {
! CHECK: br ^[[BB1:.*]]
! CHECK-NEXT: ^[[BB1]]:
! CHECK: cond_br %{{.*}}, ^[[BB2:.*]], ^[[BB4:.*]]
! CHECK-NEXT: ^[[BB2]]:
! CHECK: cond_br %{{.*}}, ^[[BB4]], ^[[BB3:.*]]
! CHECK-NEXT: ^[[BB3]]:
! CHECK: br ^bb1
! CHECK-NEXT: ^[[BB4]]:
! CHECK: omp.yield
! CHECK: }
! CHECK: omp.terminator
! CHECK: }
! CHECK: br ^[[BB1_OUTER]]
! CHECK-NEXT: ^[[BB3_OUTER]]:
! CHECK-NEXT: return
subroutine ss7() ! EXIT inside OpenMP parallel do (inside do loop)
integer :: x
do i = 1, 3
!$omp parallel do private(x)
do j = 1, 3
x = j * i
do k = 1, 3
if (k .eq. n) exit
x = k
x = x + k
enddo
enddo
!$omp end parallel do
enddo
end

! CHECK-LABEL: func @_QPss8() {
! CHECK: omp.parallel {
! CHECK: omp.wsloop {{.*}} {
! CHECK: br ^[[BB1:.*]]
! CHECK: ^[[BB1]]:
! CHECK: cond_br %{{.*}}, ^[[BB2:.*]], ^[[BB4:.*]]
! CHECK: ^[[BB2]]:
! CHECK: cond_br %{{.*}}, ^[[BB4]], ^[[BB3:.*]]
! CHECK: ^[[BB3]]:
! CHECK: br ^[[BB1]]
! CHECK: ^[[BB4]]:
! CHECK: omp.yield
! CHECK: }
! CHECK: omp.terminator
! CHECK: }
subroutine ss8() ! EXIT inside OpenMP parallel do
integer :: x
!$omp parallel do private(x)
do j = 1, 3
x = j * i
do k = 1, 3
if (k .eq. n) exit
x = k
x = x + k
enddo
enddo
!$omp end parallel do
end

! CHECK-LABEL: func @_QPss9() {
! CHECK: omp.parallel {
! CHECK-NEXT: omp.parallel {
! CHECK: br ^[[BB1:.*]]
! CHECK: ^[[BB1]]:
! CHECK: cond_br %{{.*}}, ^[[BB2:.*]], ^[[BB4:.*]]
! CHECK-NEXT: ^[[BB2]]:
! CHECK: cond_br %{{.*}}, ^[[BB4]], ^[[BB3:.*]]
! CHECK-NEXT: ^[[BB3]]:
! CHECK: br ^[[BB1]]
! CHECK-NEXT: ^[[BB4]]:
! CHECK: omp.terminator
! CHECK-NEXT: }
! CHECK: omp.terminator
! CHECK-NEXT }
! CHECK: }
subroutine ss9() ! EXIT inside OpenMP parallel (inside parallel)
integer :: x
!$omp parallel
!$omp parallel private(x)
do k = 1, 3
if (k .eq. n) exit
x = k
x = x + k
end do
!$omp end parallel
!$omp end parallel
end

! CHECK-LABEL: func @_QQmain
program p
call ss1(2)
call ss2(2)
call ss3(2)
call ss4(2)
call ss5()
call ss6()
call ss7()
call ss8()
call ss9()
end