Adds support for lowering `do concurrent` nests from PFT to the new
`fir.do_concurrent` MLIR op as well as its special terminator
`fir.do_concurrent.loop` which models the actual loop nest.
To that end, this PR emits the allocations for the iteration variables
within the block of the `fir.do_concurrent` op and creates a region for
the `fir.do_concurrent.loop` op that accepts arguments equal in number
to the number of the input `do concurrent` iteration ranges.
For example, given the following input:
```fortran
do concurrent(i=1:10, j=11:20)
end do
```
the changes in this PR emit the following MLIR:
```mlir
fir.do_concurrent {
%22 = fir.alloca i32 {bindc_name = "i"}
%23:2 = hlfir.declare %22 {uniq_name = "_QFsub1Ei"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
%24 = fir.alloca i32 {bindc_name = "j"}
%25:2 = hlfir.declare %24 {uniq_name = "_QFsub1Ej"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
fir.do_concurrent.loop (%arg1, %arg2) = (%18, %20) to (%19, %21) step (%c1, %c1_0) {
%26 = fir.convert %arg1 : (index) -> i32
fir.store %26 to %23#0 : !fir.ref<i32>
%27 = fir.convert %arg2 : (index) -> i32
fir.store %27 to %25#0 : !fir.ref<i32>
}
}
```
93 lines
2.3 KiB
Fortran
93 lines
2.3 KiB
Fortran
! Fails until we update the pass to use the `fir.do_concurrent` op.
|
|
! XFAIL: *
|
|
|
|
! Tests loop-nest detection algorithm for do-concurrent mapping.
|
|
|
|
! REQUIRES: asserts
|
|
|
|
! RUN: %flang_fc1 -emit-hlfir -fopenmp -fdo-concurrent-to-openmp=host \
|
|
! RUN: -mmlir -debug -mmlir -mlir-disable-threading %s -o - 2> %t.log || true
|
|
|
|
! RUN: FileCheck %s < %t.log
|
|
|
|
program main
|
|
implicit none
|
|
|
|
contains
|
|
|
|
subroutine foo(n)
|
|
implicit none
|
|
integer :: n, m
|
|
integer :: i, j, k
|
|
integer :: x
|
|
integer, dimension(n) :: a
|
|
integer, dimension(n, n, n) :: b
|
|
|
|
! CHECK: Loop pair starting at location
|
|
! CHECK: loc("{{.*}}":[[# @LINE + 1]]:{{.*}}) is perfectly nested
|
|
do concurrent(i=1:n, j=1:bar(n*m, n/m))
|
|
a(i) = n
|
|
end do
|
|
|
|
! CHECK: Loop pair starting at location
|
|
! CHECK: loc("{{.*}}":[[# @LINE + 1]]:{{.*}}) is perfectly nested
|
|
do concurrent(i=bar(n, x):n, j=1:bar(n*m, n/m))
|
|
a(i) = n
|
|
end do
|
|
|
|
! CHECK: Loop pair starting at location
|
|
! CHECK: loc("{{.*}}":[[# @LINE + 1]]:{{.*}}) is not perfectly nested
|
|
do concurrent(i=bar(n, x):n)
|
|
do concurrent(j=1:bar(n*m, n/m))
|
|
a(i) = n
|
|
end do
|
|
end do
|
|
|
|
! CHECK: Loop pair starting at location
|
|
! CHECK: loc("{{.*}}":[[# @LINE + 1]]:{{.*}}) is not perfectly nested
|
|
do concurrent(i=1:n)
|
|
x = 10
|
|
do concurrent(j=1:m)
|
|
b(i,j,k) = i * j + k
|
|
end do
|
|
end do
|
|
|
|
! CHECK: Loop pair starting at location
|
|
! CHECK: loc("{{.*}}":[[# @LINE + 1]]:{{.*}}) is not perfectly nested
|
|
do concurrent(i=1:n)
|
|
do concurrent(j=1:m)
|
|
b(i,j,k) = i * j + k
|
|
end do
|
|
x = 10
|
|
end do
|
|
|
|
! CHECK: Loop pair starting at location
|
|
! CHECK: loc("{{.*}}":[[# @LINE + 1]]:{{.*}}) is not perfectly nested
|
|
do concurrent(i=1:n)
|
|
do concurrent(j=1:m)
|
|
b(i,j,k) = i * j + k
|
|
x = 10
|
|
end do
|
|
end do
|
|
|
|
! Verify the (i,j) and (j,k) pairs of loops are detected as perfectly nested.
|
|
!
|
|
! CHECK: Loop pair starting at location
|
|
! CHECK: loc("{{.*}}":[[# @LINE + 3]]:{{.*}}) is perfectly nested
|
|
! CHECK: Loop pair starting at location
|
|
! CHECK: loc("{{.*}}":[[# @LINE + 1]]:{{.*}}) is perfectly nested
|
|
do concurrent(i=bar(n, x):n, j=1:bar(n*m, n/m), k=1:bar(n*m, bar(n*m, n/m)))
|
|
a(i) = n
|
|
end do
|
|
end subroutine
|
|
|
|
pure function bar(n, m)
|
|
implicit none
|
|
integer, intent(in) :: n, m
|
|
integer :: bar
|
|
|
|
bar = n + m
|
|
end function
|
|
|
|
end program main
|