llvm-project/flang/test/Semantics/omp-symbol08.f90

Ignoring revisions in .git-blame-ignore-revs. Click here to bypass and see the normal blame view.

252 lines
7.7 KiB
Fortran
Raw Normal View History

! RUN: %S/test_symbols.sh %s %t %flang_fc1 -fopenmp
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
! 2.15.1.1 Predetermined rules for associated do-loops index variable
! a) The loop iteration variable(s) in the associated do-loop(s) of a do,
! parallel do, taskloop, or distribute construct is (are) private.
! b) The loop iteration variable in the associated do-loop of a simd construct
! with just one associated do-loop is linear with a linear-step that is the
! increment of the associated do-loop.
! c) The loop iteration variables in the associated do-loops of a simd
! construct with multiple associated do-loops are lastprivate.
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
! d) A loop iteration variable for a sequential loop in a parallel or task
! generating construct is private in the innermost such construct that
! encloses the loop.
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
! - TBD
! All the tests assume that the do-loops association for collapse/ordered
! clause has been performed (the number of nested do-loops >= n).
! Rule a)
! TODO: nested constructs (k should be private too)
!DEF: /test_do (Subroutine) Subprogram
subroutine test_do
implicit none
!DEF: /test_do/a ObjectEntity REAL(4)
real a(20,20,20)
!DEF: /test_do/i ObjectEntity INTEGER(4)
!DEF: /test_do/j ObjectEntity INTEGER(4)
!DEF: /test_do/k ObjectEntity INTEGER(4)
integer i, j, k
!$omp parallel
!REF: /test_do/i
i = 99
!$omp do collapse(2)
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_do/Block1/Block1/i (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
do i=1,5
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_do/Block1/Block1/j (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
do j=6,10
!REF: /test_do/a
a(1,1,1) = 0.
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_do/Block1/k (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
do k=11,15
!REF: /test_do/a
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!REF: /test_do/Block1/k
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
!REF: /test_do/Block1/Block1/j
!REF: /test_do/Block1/Block1/i
a(k,j,i) = 1.
end do
end do
end do
!$omp end parallel
end subroutine test_do
! Rule a)
!DEF: /test_pardo (Subroutine) Subprogram
subroutine test_pardo
implicit none
!DEF: /test_pardo/a ObjectEntity REAL(4)
real a(20,20,20)
!DEF: /test_pardo/i ObjectEntity INTEGER(4)
!DEF: /test_pardo/j ObjectEntity INTEGER(4)
!DEF: /test_pardo/k ObjectEntity INTEGER(4)
integer i, j, k
!$omp parallel do collapse(2) private(k) ordered(2)
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_pardo/Block1/i (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
do i=1,5
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_pardo/Block1/j (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
do j=6,10
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
!REF: /test_pardo/a
a(1,1,1) = 0.
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_pardo/Block1/k (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
do k=11,15
!REF: /test_pardo/a
!REF: /test_pardo/Block1/k
!REF: /test_pardo/Block1/j
!REF: /test_pardo/Block1/i
a(k,j,i) = 1.
end do
end do
end do
end subroutine test_pardo
! Rule a)
!DEF: /test_taskloop (Subroutine) Subprogram
subroutine test_taskloop
implicit none
!DEF: /test_taskloop/a ObjectEntity REAL(4)
real a(5,5)
!DEF: /test_taskloop/i ObjectEntity INTEGER(4)
!DEF: /test_taskloop/j ObjectEntity INTEGER(4)
integer i, j
!$omp taskloop private(j)
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_taskloop/Block1/i (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
do i=1,5
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_taskloop/Block1/j (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
!REF: /test_taskloop/Block1/i
do j=1,i
!REF: /test_taskloop/a
!REF: /test_taskloop/Block1/j
!REF: /test_taskloop/Block1/i
a(j,i) = 3.14
end do
end do
!$omp end taskloop
end subroutine test_taskloop
! Rule a); OpenMP 4.5 Examples teams.2.f90
! TODO: reduction; data-mapping attributes
!DEF: /dotprod (Subroutine) Subprogram
!DEF: /dotprod/b ObjectEntity REAL(4)
!DEF: /dotprod/c ObjectEntity REAL(4)
!DEF: /dotprod/n ObjectEntity INTEGER(4)
!DEF: /dotprod/block_size ObjectEntity INTEGER(4)
!DEF: /dotprod/num_teams ObjectEntity INTEGER(4)
!DEF: /dotprod/block_threads ObjectEntity INTEGER(4)
subroutine dotprod (b, c, n, block_size, num_teams, block_threads)
implicit none
!REF: /dotprod/n
integer n
!REF: /dotprod/b
!REF: /dotprod/n
!REF: /dotprod/c
!DEF: /dotprod/sum ObjectEntity REAL(4)
real b(n), c(n), sum
!REF: /dotprod/block_size
!REF: /dotprod/num_teams
!REF: /dotprod/block_threads
!DEF: /dotprod/i ObjectEntity INTEGER(4)
!DEF: /dotprod/i0 ObjectEntity INTEGER(4)
integer block_size, num_teams, block_threads, i, i0
!REF: /dotprod/sum
sum = 0.0e0
!$omp target map(to:b,c) map(tofrom:sum)
!$omp teams num_teams(num_teams) thread_limit(block_threads) reduction(+:sum)
!$omp distribute
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /dotprod/Block1/Block1/Block1/i0 (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
!REF: /dotprod/n
!REF: /dotprod/block_size
do i0=1,n,block_size
!$omp parallel do reduction(+:sum)
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /dotprod/Block1/Block1/Block1/Block1/i (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
!REF: /dotprod/Block1/Block1/Block1/i0
!DEF: /dotprod/min ELEMENTAL, INTRINSIC, PURE (Function) ProcEntity
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
!REF: /dotprod/block_size
!REF: /dotprod/n
do i=i0,min(i0+block_size, n)
!DEF: /dotprod/Block1/Block1/Block1/Block1/sum (OmpReduction) HostAssoc REAL(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
!REF: /dotprod/b
!REF: /dotprod/Block1/Block1/Block1/Block1/i
!REF: /dotprod/c
sum = sum+b(i)*c(i)
end do
end do
!$omp end teams
!$omp end target
!REF: /dotprod/sum
print *, sum
end subroutine dotprod
! Rule b)
! TODO: nested constructs (j, k should be private too)
!DEF: /test_simd (Subroutine) Subprogram
subroutine test_simd
implicit none
!DEF: /test_simd/a ObjectEntity REAL(4)
real a(20,20,20)
!DEF: /test_simd/i ObjectEntity INTEGER(4)
!DEF: /test_simd/j ObjectEntity INTEGER(4)
!DEF: /test_simd/k ObjectEntity INTEGER(4)
integer i, j, k
!$omp parallel do simd
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_simd/Block1/i (OmpLinear, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
do i=1,5
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_simd/Block1/j (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
do j=6,10
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_simd/Block1/k (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
do k=11,15
!REF: /test_simd/a
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!REF: /test_simd/Block1/k
!REF: /test_simd/Block1/j
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
!REF: /test_simd/Block1/i
a(k,j,i) = 3.14
end do
end do
end do
end subroutine test_simd
! Rule c)
!DEF: /test_simd_multi (Subroutine) Subprogram
subroutine test_simd_multi
implicit none
!DEF: /test_simd_multi/a ObjectEntity REAL(4)
real a(20,20,20)
!DEF: /test_simd_multi/i ObjectEntity INTEGER(4)
!DEF: /test_simd_multi/j ObjectEntity INTEGER(4)
!DEF: /test_simd_multi/k ObjectEntity INTEGER(4)
integer i, j, k
!$omp parallel do simd collapse(3)
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_simd_multi/Block1/i (OmpLastPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
do i=1,5
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_simd_multi/Block1/j (OmpLastPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
do j=6,10
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
!DEF: /test_simd_multi/Block1/k (OmpLastPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
[flang] [OpenMP] Predetermined rules for loop index variables (flang-compiler/f18#962) This refers to three rules in OpenMP 4.5 Spec 2.15.1.1: * The loop iteration variable(s) in the associated do-loop(s) of a do, parallel do, taskloop, or distribute construct is (are) private. * The loop iteration variable in the associated do-loop of a simd construct with just one associated do-loop is linear with a linear-step that is the increment of the associated do-loop. * The loop iteration variables in the associated do-loops of a simd construct with multiple associated do-loops are lastprivate. A simple example: ``` implicit none integer :: N = 1024 integer i, j, k !$omp parallel do collapse(3) do i=1, N <- i is private do j=1, N <- j is private do k=1, N <- k is private enddo enddo enddo end ``` If `collapse` clause is not present, the associated do-loop for construct `parallel do` is only `i` loop. With `collapse(n)`, `i`, `j`, and `k` are all associated do-loops and the loop index variables are private to the OpenMP construct: ``` implicit none !DEF: /MainProgram1/n ObjectEntity INTEGER(4) integer :: n = 1024 !DEF: /MainProgram1/i ObjectEntity INTEGER(4) !DEF: /MainProgram1/j ObjectEntity INTEGER(4) !DEF: /MainProgram1/k ObjectEntity INTEGER(4) integer i, j, k !$omp parallel do collapse(3) !DEF: /MainProgram1/Block1/i (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do i=1,n !DEF: /MainProgram1/Block1/j (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do j=1,n !DEF: /MainProgram1/Block1/k (OmpPrivate) HostAssoc INTEGER(4) !REF: /MainProgram1/n do k=1,n end do end do end do end program ``` This implementation assumes that the structural checks for do-loops are done at this point, for example the `n` in `collapse(n)` should be no more than the number of actual perfectly nested do-loops, etc.. Original-commit: flang-compiler/f18@572a57d3d0d785bb3f2aad9e890ef498c1214309 Reviewed-on: https://github.com/flang-compiler/f18/pull/962
2020-02-06 02:13:43 +08:00
do k=11,15
!REF: /test_simd_multi/a
!REF: /test_simd_multi/Block1/k
!REF: /test_simd_multi/Block1/j
!REF: /test_simd_multi/Block1/i
a(k,j,i) = 3.14
end do
end do
end do
end subroutine test_simd_multi
[flang] [OpenMP] Predetermined rule for sequential loop index (flang-compiler/f18#976) This commit implements rule: A loop iteration variable for a sequential loop in a parallel or task generating construct is private in the innermost such construct that encloses the loop. A Simple example: ``` i = -1 <== Scope 0 j = -1 !$omp parallel <== Scope 1 print *,i,j <-- both are shared (Scope 0) !$omp parallel <== Scope 2 print *,i,j <-- a) i is shared (Scope 0), j is private (Scope 2) !$omp do <== Scope 3 do i=1, 10 <-- i is private (Scope 3) do j=1, 10 <-- b) j is private (Scope 2, not 3!) enddo enddo print *,i,j <-- c) i is shared (Scope 0), j is private (Scope 2) !$omp end parallel print *,i,j <-- both are shared (Scope 0) !$omp end parallel print *,i,j <-- both are shared (Scope 0) end ``` Ideally the above rule solves a), b), and c) but a) is left as a TODO because it is better to handle the data-sharing attribute conflicts along with the rules for "Predetermined DSA on Clauses". The basic idea is when visiting the `DoConstruct` node within an OpenMP construct, if the do-loop is not associated (like `i` loop is associated with `!$omp do`) AND the do-loop is in the parallel/task generating construct, resolve the loop index to be private to that innermost construct. In the above example, `j` loop is not associated (then it is sequential) and the innermost parallel/task generating construct that encloses the `j` loop is the `parallel` construct marked with `<== Scope 2`, so `j` is private to that construct. To do that, I also need to change the prototype of those `ResolveOmp*` functions to allow specifiying the `scope` because the new symbol for `j` should be created in Scope 2 and all the `symbol` field of `Name j` in that `parallel` construct should be fixed, such as c). Original-commit: flang-compiler/f18@69a845283b058a3644053ec58b00d3361f4d4a59 Reviewed-on: https://github.com/flang-compiler/f18/pull/976
2020-02-19 08:27:43 +08:00
! Rule d)
!DEF: /test_seq_loop (Subroutine) Subprogram
subroutine test_seq_loop
implicit none
!DEF: /test_seq_loop/i ObjectEntity INTEGER(4)
!DEF: /test_seq_loop/j ObjectEntity INTEGER(4)
integer i, j
!REF: /test_seq_loop/i
i = -1
!REF: /test_seq_loop/j
j = -1
!$omp parallel
!REF: /test_seq_loop/i
!REF: /test_seq_loop/j
print *, i, j
!$omp parallel
!REF: /test_seq_loop/i
!DEF: /test_seq_loop/Block1/Block1/j (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
print *, i, j
!$omp do
!DEF: /test_seq_loop/Block1/Block1/Block1/i (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
do i=1,10
!REF: /test_seq_loop/Block1/Block1/j
do j=1,10
end do
end do
!REF: /test_seq_loop/i
!REF: /test_seq_loop/Block1/Block1/j
print *, i, j
!$omp end parallel
!REF: /test_seq_loop/i
!REF: /test_seq_loop/j
print *, i, j
!$omp end parallel
!REF: /test_seq_loop/i
!REF: /test_seq_loop/j
print *, i, j
end subroutine test_seq_loop