llvm-project/flang/test/Semantics/omp-device-constructs.f90

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

186 lines
4.2 KiB
Fortran
Raw Normal View History

[flang] A rework of the cmake build components for in and out of tree builds. In general all the basic functionality seems to work and removes some redundancy and more complicated features in favor of borrowing infrastructure from LLVM build configurations. Here's a quick summary of details and remaining issues: * Testing has spanned Ubuntu 18.04 & 19.10, CentOS 7, RHEL 8, and MacOS/darwin. Architectures include x86_64 and Arm. Without access to Window nothing has been tested there yet. * As we change file and directory naming schemes (i.e., capitalization) some odd things can occur on MacOS systems with case preserving but not case senstive file system configurations. Can be painful and certainly something to watch out for as any any such changes continue. * Testing infrastructure still needs to be tuned up and worked on. Note that there do appear to be cases of some tests hanging (on MacOS in particular). They appear unrelated to the build process. * Shared library configurations need testing (and probably fixing). * Tested both standalone and 'in-mono repo' builds. Changes for supporting the mono repo builds will require LLVM-level changes that are straightforward when the time comes. * The configuration contains a work-around for LLVM's C++ standard mode passing down into Flang/F18 builds (i.e., LLVM CMake configuration would force a -std=c++11 flag to show up in command line arguments. The current configuration removes that automatically and is more strict in following new CMake guidelines for enforcing C++17 mode across all the CMake files. * Cleaned up a lot of repetition in the command line arguments. It is likely that more work is still needed to both allow for customization and working around CMake defailts (or those inherited from LLVM's configuration files). On some platforms agressive optimization flags (e.g. -O3) can actually break builds due to the inlining of templates in .cpp source files that then no longer are available for use cases outside those source files (shows up as link errors). Sticking at -O2 appears to fix this. Currently this CMake configuration forces this in release mode but at the cost of stomping on any CMake, or user customized, settings for the release flags. * Made the lit tests non-source directory dependent where appropriate. This is done by configuring certain test shell files to refer to the correct paths whether an in or out of tree build is being performed. These configured files are output in the build directory. A %B substitution is introduced in lit to refer to the build directory, mirroring the %S substitution for the source directory, so that the tests can refer to the configured shell scripts. Co-authored-by: David Truby <david.truby@arm.com> Original-commit: flang-compiler/f18@d1c7184159b2d3c542a8f36c58a0c817e7506845 Reviewed-on: https://github.com/flang-compiler/f18/pull/1045
2020-02-26 07:22:14 +08:00
! RUN: %B/test/Semantics/test_errors.sh %s %flang %t
! OPTIONS: -fopenmp
! Check OpenMP clause validity for the following directives:
! 2.10 Device constructs
program main
real(8) :: arrayA(256), arrayB(256)
integer :: N
arrayA = 1.414
arrayB = 3.14
N = 256
!$omp target map(arrayA)
do i = 1, N
a = 3.14
enddo
!$omp end target
!$omp target device(0)
do i = 1, N
a = 3.14
enddo
!$omp end target
!ERROR: At most one DEVICE clause can appear on the TARGET directive
!$omp target device(0) device(1)
do i = 1, N
a = 3.14
enddo
!$omp end target
!ERROR: SCHEDULE clause is not allowed on the TARGET directive
!$omp target schedule(static)
do i = 1, N
a = 3.14
enddo
!$omp end target
!$omp target defaultmap(tofrom:scalar)
do i = 1, N
a = 3.14
enddo
!$omp end target
!ERROR: The argument TOFROM:SCALAR must be specified on the DEFAULTMAP clause
!$omp target defaultmap(tofrom)
do i = 1, N
a = 3.14
enddo
!$omp end target
!ERROR: At most one DEFAULTMAP clause can appear on the TARGET directive
!$omp target defaultmap(tofrom:scalar) defaultmap(tofrom:scalar)
do i = 1, N
a = 3.14
enddo
!$omp end target
!$omp teams num_teams(3) thread_limit(10) default(shared) private(i) shared(a)
do i = 1, N
a = 3.14
enddo
!$omp end teams
!ERROR: At most one NUM_TEAMS clause can appear on the TEAMS directive
!$omp teams num_teams(2) num_teams(3)
do i = 1, N
a = 3.14
enddo
!$omp end teams
!ERROR: The parameter of the NUM_TEAMS clause must be a positive integer expression
!$omp teams num_teams(-1)
do i = 1, N
a = 3.14
enddo
!$omp end teams
!ERROR: At most one THREAD_LIMIT clause can appear on the TEAMS directive
!$omp teams thread_limit(2) thread_limit(3)
do i = 1, N
a = 3.14
enddo
!$omp end teams
!ERROR: The parameter of the THREAD_LIMIT clause must be a positive integer expression
!$omp teams thread_limit(-1)
do i = 1, N
a = 3.14
enddo
!$omp end teams
!ERROR: At most one DEFAULT clause can appear on the TEAMS directive
[flang] [OpenMP] Name Resolution for OpenMP constructs (flang-compiler/f18#940) This is an extended framework based on the previous work that addresses the NR on OpenMP directives/clauses (b2ea520). In this change: * New `OmpVisitor` is created (ResolveNamesVisitor derives from it) to create necessary scopes for certain OpenMP constructs. This is along with the regular Fortran NR process. * Old `OmpVisitor` is adjusted and converted to a standalone visitor-- `OmpAttributeVisitor`. This is used to walk through the OpenMP constructs and do the NR for variables on the OpenMP directives or data references within the OpenMP constructs. "Do the NR" here means that based on the NR results of the regular Fortran NR, fix the symbols of `Names` related to the OpenMP constructs. Note that there is an `OmpContext` in this visitor (similar to the one in `OmpStructureChecker`), this is necessary when dealing with the nested OpenMP constructs in the future. Given an OpenMP code: ``` real*8 a, b a = 1. b = 2. !$omp parallel private(a) a = 3. b = 4. !$omp end parallel print *, a, b end ``` w/o -fopenmp: ``` real*8 a, b !REF: /MainProgram1/a a = 1. !REF: /MainProgram1/b b = 2. !!!! OMP parallel !REF: /MainProgram1/a a = 3. !REF: /MainProgram1/b b = 4. !!!! OMP end parallel !REF: /MainProgram1/a !REF: /MainProgram1/b print *, a, b end ``` w/ -fopenmp: ``` real*8 a, b !REF: /MainProgram1/a a = 1. !REF: /MainProgram1/b b = 2. !$omp parallel private(a) <-- new Symbol for 'a' created !DEF: /MainProgram1/Block1/a (OmpPrivate) HostAssoc REAL(8) a = 3. <-- fix the old symbol with new Symbol in parallel scope !REF: /MainProgram1/b b = 4. <-- do nothing because by default it is shared in this scope !$omp end parallel !REF: /MainProgram1/a !REF: /MainProgram1/b print *, a, b end ``` Please note that this is a framework update, there are still many things on the TODO list for finishing the NR for OpenMP (based on the `OpenMP-semantics.md` design doc), which will be on top of this framework. Some TODO items: - Create a generic function to go through all the rules for deciding `predetermined`, `explicitly determined`, and `implicitly determined` data-sharing attributes. (This is the next biggest part) - Handle `Array Sections` and `Array or Structure Element`. - Take association into consideration for example Pointer association, `ASSOCIATE` construct, and etc. - Handle all the name resolution for directives/clauses that have `parser::Name`. * N.B. Extend `AddSourceRange` to apply to current and parent scopes - motivated by a few cases that need to call `AddSourceRange` for current & parent scopes; the extension should be safe - global scope is not included Original-commit: flang-compiler/f18@0c3c39d30e3f166a6a1303337c5fd7eead720fd0 Reviewed-on: https://github.com/flang-compiler/f18/pull/940
2020-01-29 04:51:35 +08:00
!$omp teams default(shared) default(private)
do i = 1, N
a = 3.14
enddo
!$omp end teams
!$omp target teams num_teams(2) defaultmap(tofrom:scalar)
do i = 1, N
a = 3.14
enddo
!$omp end target teams
!$omp target map(tofrom:a)
do i = 1, N
a = 3.14
enddo
!$omp end target
!ERROR: Only the TO, FROM, TOFROM, or ALLOC map types are permitted for MAP clauses on the TARGET directive
!$omp target map(delete:a)
do i = 1, N
a = 3.14
enddo
!$omp end target
!$omp target data device(0) map(to:a)
do i = 1, N
a = 3.14
enddo
!$omp end target data
!ERROR: At least one MAP clause must appear on the TARGET DATA directive
!$omp target data device(0)
do i = 1, N
a = 3.14
enddo
!$omp end target data
!ERROR: At most one IF clause can appear on the TARGET ENTER DATA directive
!$omp target enter data map(to:a) if(.true.) if(.false.)
!ERROR: Only the TO or ALLOC map types are permitted for MAP clauses on the TARGET ENTER DATA directive
!$omp target enter data map(from:a)
!$omp target exit data map(delete:a)
!ERROR: At most one DEVICE clause can appear on the TARGET EXIT DATA directive
!$omp target exit data map(from:a) device(0) device(1)
!ERROR: Only the FROM, RELEASE, or DELETE map types are permitted for MAP clauses on the TARGET EXIT DATA directive
!$omp target exit data map(to:a)
!$omp target
!$omp distribute
do i = 1, N
a = 3.14
enddo
!$omp end distribute
!$omp end target
!$omp target
!ERROR: At most one COLLAPSE clause can appear on the DISTRIBUTE directive
!$omp distribute collapse(2) collapse(3)
do i = 1, N
[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 = 1, N
do k = 1, N
a = 3.14
enddo
enddo
enddo
!$omp end distribute
!$omp end target
!$omp target
!$omp distribute dist_schedule(static, 2)
do i = 1, N
a = 3.14
enddo
!$omp end distribute
!$omp end target
!$omp target
!ERROR: At most one DIST_SCHEDULE clause can appear on the DISTRIBUTE directive
!$omp distribute dist_schedule(static, 2) dist_schedule(static, 3)
do i = 1, N
a = 3.14
enddo
!$omp end distribute
!$omp end target
end program main