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

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

38 lines
1.1 KiB
Fortran
Raw Normal View History

! RUN: %S/test_symbols.sh %s %t %f18 -fopenmp
[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
! Generic tests
! 1. subroutine or function calls should not be fixed for DSA or DMA
!DEF: /foo (Function) Subprogram REAL(4)
!DEF: /foo/rnum ObjectEntity REAL(4)
function foo(rnum)
!REF: /foo/rnum
real rnum
!REF: /foo/rnum
rnum = rnum+1.
end function foo
!DEF: /function_call_in_region EXTERNAL (Subroutine) Subprogram
subroutine function_call_in_region
implicit none
!DEF: /function_call_in_region/foo (Function) ProcEntity REAL(4)
real foo
!DEF: /function_call_in_region/a ObjectEntity REAL(4)
real :: a = 0.
!DEF: /function_call_in_region/b ObjectEntity REAL(4)
real :: b = 5.
!$omp parallel default(none) private(a) shared(b)
!DEF: /function_call_in_region/Block1/a (OmpPrivate) HostAssoc REAL(4)
!REF: /function_call_in_region/foo
!REF: /function_call_in_region/b
a = foo(b)
!$omp end parallel
!REF: /function_call_in_region/a
!REF: /function_call_in_region/b
print *, a, b
end subroutine function_call_in_region
!DEF: /mm MainProgram
program mm
!REF: /function_call_in_region
call function_call_in_region
end program mm