llvm/flang/test/Semantics/dosemantics02.f90
Tim Keith 99aa87a5b5 [flang][NFC] Simplify semantics test scripts
There were several different ways of handling the option to f18 to
find predefined modules:
- test_errors.sh was created by cmake substituting
  FLANG_INTRINSIC_MODULES_DIR into test_errors.sh.in
- some tests used the flang script which has the option built it
- some tests used %f18_with_includes which was replaced by the path
  to f18 plus the -I option
- some included -I../../include/flang in their run command

To make this more consistent, change %f18 to include the
-intrinsic-module-directory option and use it everywhere, including
to replace %flang and %f18_with_includes. This requires changing all
of the invocations of the test scripts to put %f18 at the end so that
it can expand to more than one argument.

This eliminates the need to generate test_errors.sh which means we
don't need flang/test/Semantics/CMakeLists.txt or the %B substitution.
That makes the test_errors.sh command like the others, replacing
%B/test/Semantics/test_errors.sh with %S/test_errors.sh.

Also remove the OPTIONS: functionality as custom options can be included
in the RUN: command. And remove -I/../../include/flang as that is now
always included.

Differential Revision: https://reviews.llvm.org/D79634
2020-05-11 11:49:25 -07:00

43 lines
1.1 KiB
Fortran

! RUN: %S/test_errors.sh %s %t %f18
! C1121 -- any procedure referenced in a concurrent header must be pure
! Also, check that the step expressions are not zero. This is prohibited by
! Section 11.1.7.4.1, paragraph 1.
SUBROUTINE do_concurrent_c1121(i,n)
IMPLICIT NONE
INTEGER :: i, n, flag
!ERROR: DO CONCURRENT mask expression may not reference impure procedure 'random'
DO CONCURRENT (i = 1:n, random() < 3)
flag = 3
END DO
CONTAINS
IMPURE FUNCTION random() RESULT(i)
INTEGER :: i
i = 35
END FUNCTION random
END SUBROUTINE do_concurrent_c1121
SUBROUTINE s1()
INTEGER, PARAMETER :: constInt = 0
! Warn on this one for backwards compatibility
DO 10 I = 1, 10, 0
10 CONTINUE
! Warn on this one for backwards compatibility
DO 20 I = 1, 10, 5 - 5
20 CONTINUE
! Error, no compatibility requirement for DO CONCURRENT
!ERROR: DO CONCURRENT step expression may not be zero
DO CONCURRENT (I = 1 : 10 : 0)
END DO
! Error, this time with an integer constant
!ERROR: DO CONCURRENT step expression may not be zero
DO CONCURRENT (I = 1 : 10 : constInt)
END DO
end subroutine s1