llvm-project/flang/test/Semantics/doconcurrent01.f90
Patrick McCormick 6c16aa4f67 [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@d1c7184159
Reviewed-on: https://github.com/flang-compiler/f18/pull/1045
2020-03-26 18:17:04 +00:00

243 lines
6.6 KiB
Fortran

! RUN: %B/test/Semantics/test_errors.sh %s %flang %t
! C1141
! A reference to the procedure IEEE_SET_HALTING_MODE ! from the intrinsic
! module IEEE_EXCEPTIONS, shall not ! appear within a DO CONCURRENT construct.
!
! C1137
! An image control statement shall not appear within a DO CONCURRENT construct.
!
! C1136
! A RETURN statement shall not appear within a DO CONCURRENT construct.
!
! (11.1.7.5), paragraph 4
! In a DO CONCURRENT, can't have an i/o statement with an ADVANCE= specifier
subroutine do_concurrent_test1(i,n)
implicit none
integer :: i, n
do 10 concurrent (i = 1:n)
!ERROR: An image control statement is not allowed in DO CONCURRENT
SYNC ALL
!ERROR: An image control statement is not allowed in DO CONCURRENT
SYNC IMAGES (*)
!ERROR: An image control statement is not allowed in DO CONCURRENT
SYNC MEMORY
!ERROR: RETURN is not allowed in DO CONCURRENT
return
10 continue
end subroutine do_concurrent_test1
subroutine do_concurrent_test2(i,j,n,flag)
use ieee_exceptions
use iso_fortran_env, only: team_type
implicit none
integer :: i, n
type(ieee_flag_type) :: flag
logical :: flagValue, halting
type(team_type) :: j
type(ieee_status_type) :: status
do concurrent (i = 1:n)
!ERROR: An image control statement is not allowed in DO CONCURRENT
sync team (j)
!ERROR: An image control statement is not allowed in DO CONCURRENT
change team (j)
!ERROR: An image control statement is not allowed in DO CONCURRENT
critical
!ERROR: Call to an impure procedure is not allowed in DO CONCURRENT
call ieee_get_status(status)
!ERROR: IEEE_SET_HALTING_MODE is not allowed in DO CONCURRENT
call ieee_set_halting_mode(flag, halting)
end critical
end team
!ERROR: ADVANCE specifier is not allowed in DO CONCURRENT
write(*,'(a35)',advance='no')
end do
! The following is OK
do concurrent (i = 1:n)
call ieee_set_flag(flag, flagValue)
end do
end subroutine do_concurrent_test2
subroutine s1()
use iso_fortran_env
type(event_type) :: x
do concurrent (i = 1:n)
!ERROR: An image control statement is not allowed in DO CONCURRENT
event post (x)
end do
end subroutine s1
subroutine s2()
use iso_fortran_env
type(event_type) :: x
do concurrent (i = 1:n)
!ERROR: An image control statement is not allowed in DO CONCURRENT
event wait (x)
end do
end subroutine s2
subroutine s3()
use iso_fortran_env
type(team_type) :: t
do concurrent (i = 1:n)
!ERROR: An image control statement is not allowed in DO CONCURRENT
form team(1, t)
end do
end subroutine s3
subroutine s4()
use iso_fortran_env
type(lock_type) :: l
do concurrent (i = 1:n)
!ERROR: An image control statement is not allowed in DO CONCURRENT
lock(l)
!ERROR: An image control statement is not allowed in DO CONCURRENT
unlock(l)
end do
end subroutine s4
subroutine s5()
do concurrent (i = 1:n)
!ERROR: An image control statement is not allowed in DO CONCURRENT
stop
end do
end subroutine s5
subroutine s6()
type :: type0
integer, allocatable, dimension(:) :: type0_field
integer, allocatable, dimension(:), codimension[:] :: coarray_type0_field
end type
type :: type1
type(type0) :: type1_field
end type
type(type1) :: pvar;
type(type1) :: qvar;
integer, allocatable, dimension(:) :: array1
integer, allocatable, dimension(:) :: array2
integer, allocatable, codimension[:] :: ca, cb
integer, allocatable :: aa, ab
! All of the following are allowable outside a DO CONCURRENT
allocate(array1(3), pvar%type1_field%type0_field(3), array2(9))
allocate(pvar%type1_field%coarray_type0_field(3)[*])
allocate(ca[*])
allocate(ca[*], pvar%type1_field%coarray_type0_field(3)[*])
do concurrent (i = 1:10)
allocate(pvar%type1_field%type0_field(3))
end do
do concurrent (i = 1:10)
!ERROR: An image control statement is not allowed in DO CONCURRENT
allocate(ca[*])
end do
do concurrent (i = 1:10)
!ERROR: An image control statement is not allowed in DO CONCURRENT
deallocate(ca)
end do
do concurrent (i = 1:10)
!ERROR: An image control statement is not allowed in DO CONCURRENT
allocate(pvar%type1_field%coarray_type0_field(3)[*])
end do
do concurrent (i = 1:10)
!ERROR: An image control statement is not allowed in DO CONCURRENT
deallocate(pvar%type1_field%coarray_type0_field)
end do
do concurrent (i = 1:10)
!ERROR: An image control statement is not allowed in DO CONCURRENT
allocate(ca[*], pvar%type1_field%coarray_type0_field(3)[*])
end do
do concurrent (i = 1:10)
!ERROR: An image control statement is not allowed in DO CONCURRENT
deallocate(ca, pvar%type1_field%coarray_type0_field)
end do
! Call to MOVE_ALLOC of a coarray outside a DO CONCURRENT. This is OK.
call move_alloc(ca, cb)
! Note that the errors below relating to MOVE_ALLOC() bing impure are bogus.
! They're the result of the fact that access to the move_alloc() instrinsic
! is not yet possible.
allocate(aa)
do concurrent (i = 1:10)
!ERROR: Call to an impure procedure is not allowed in DO CONCURRENT
call move_alloc(aa, ab)
end do
! Call to MOVE_ALLOC with non-coarray arguments in a DO CONCURRENT. This is OK.
do concurrent (i = 1:10)
!ERROR: Call to an impure procedure is not allowed in DO CONCURRENT
!ERROR: An image control statement is not allowed in DO CONCURRENT
call move_alloc(ca, cb)
end do
do concurrent (i = 1:10)
!ERROR: Call to an impure procedure is not allowed in DO CONCURRENT
!ERROR: An image control statement is not allowed in DO CONCURRENT
call move_alloc(pvar%type1_field%coarray_type0_field, qvar%type1_field%coarray_type0_field)
end do
end subroutine s6
subroutine s7()
interface
pure integer function pf()
end function pf
end interface
type :: procTypeNotPure
procedure(notPureFunc), pointer, nopass :: notPureProcComponent
end type procTypeNotPure
type :: procTypePure
procedure(pf), pointer, nopass :: pureProcComponent
end type procTypePure
type(procTypeNotPure) :: procVarNotPure
type(procTypePure) :: procVarPure
integer :: ivar
procVarPure%pureProcComponent => pureFunc
do concurrent (i = 1:10)
print *, "hello"
end do
do concurrent (i = 1:10)
ivar = pureFunc()
end do
! This should not generate errors
do concurrent (i = 1:10)
ivar = procVarPure%pureProcComponent()
end do
! This should generate an error
do concurrent (i = 1:10)
!ERROR: Call to an impure procedure component is not allowed in DO CONCURRENT
ivar = procVarNotPure%notPureProcComponent()
end do
contains
integer function notPureFunc()
notPureFunc = 2
end function notPureFunc
pure integer function pureFunc()
pureFunc = 3
end function pureFunc
end subroutine s7