llvm-project/flang/test/Semantics/dosemantics02.f90
Emil Kieri 93dca9fbee [flang][test] Fix semantics tests with respect to warnings
Make tests expect the (correctly) emitted warnings using the WARNING
directive. This directive is non-functional now, but will be recognised
by test_errors.py when D125804 is landed. This patch is a preparation
for D125804.

For most tests, we add missing WARNING directives for emitted warnings,
but there are exceptions:

 - for int-literals.f90 and resolve31.f90 we pass -pedantic to the
   frontend driver, so that the expected warnings are actually emitted.

 - for block-data01.f90 and resolve42.f90 we change the tests so that
   warnings, which appear unintentional, are not emitted. While testing
   the warning in question (padding added for alignment in common block)
   would be desired, that is beyond the scope of this patch. This
   warning is target-dependent.

Reviewed By: PeteSteinfeld

Differential Revision: https://reviews.llvm.org/D131987
2022-08-18 19:16:20 +02:00

45 lines
1.2 KiB
Fortran

! RUN: %python %S/test_errors.py %s %flang_fc1
! 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
!WARNING: DO step expression should not be zero
DO 10 I = 1, 10, 0
10 CONTINUE
! Warn on this one for backwards compatibility
!WARNING: DO step expression should not be zero
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