-! RUN: %python %S/../test_errors.py %s %flang -fopenmp
+! RUN: %python %S/../test_errors.py %s %flang -fopenmp -Werror
! OpenMP Version 5.0
! 2.19.4.4 firstprivate Clause
! 2.19.4.5 lastprivate Clause
subroutine firstprivate()
class(*), allocatable, save :: x
- !WARNING: If a polymorphic variable with allocatable attribute 'x' is in FIRSTPRIVATE clause, the behavior is unspecified
+ !PORTABILITY: If a polymorphic variable with allocatable attribute 'x' is in FIRSTPRIVATE clause, the behavior is unspecified
!$omp parallel firstprivate(x)
call sub()
!$omp end parallel
subroutine lastprivate()
class(*), allocatable, save :: x
- !WARNING: If a polymorphic variable with allocatable attribute 'x' is in LASTPRIVATE clause, the behavior is unspecified
+ !PORTABILITY: If a polymorphic variable with allocatable attribute 'x' is in LASTPRIVATE clause, the behavior is unspecified
!$omp do lastprivate(x)
do i = 1, 10
call sub()
class(*), allocatable, save :: x
!$omp threadprivate(x)
- !WARNING: If a polymorphic variable with allocatable attribute 'x' is in COPYIN clause, the behavior is unspecified
+ !PORTABILITY: If a polymorphic variable with allocatable attribute 'x' is in COPYIN clause, the behavior is unspecified
!$omp parallel copyin(x)
call sub()
!$omp end parallel
class(*), allocatable, save :: x
!$omp threadprivate(x)
- !WARNING: If a polymorphic variable with allocatable attribute 'x' is in COPYPRIVATE clause, the behavior is unspecified
+ !PORTABILITY: If a polymorphic variable with allocatable attribute 'x' is in COPYPRIVATE clause, the behavior is unspecified
!$omp single copyprivate(x)
call sub()
!$omp end single
-! RUN: %python %S/../test_errors.py %s %flang_fc1 -fopenmp
+! RUN: %python %S/../test_errors.py %s %flang_fc1 -fopenmp -Werror
! OpenMP Version 5.0
! Check OpenMP construct validity for the following directives:
real, allocatable :: B(:)
!$omp target
- !WARNING: If TARGET UPDATE directive is nested inside TARGET region, the behaviour is unspecified
+ !PORTABILITY: If TARGET UPDATE directive is nested inside TARGET region, the behaviour is unspecified
!$omp target update from(arrayA) to(arrayB)
do i = 1, 512
arrayA(i) = arrayB(i)
!$omp parallel
!$omp target
!$omp parallel
- !WARNING: If TARGET UPDATE directive is nested inside TARGET region, the behaviour is unspecified
+ !PORTABILITY: If TARGET UPDATE directive is nested inside TARGET region, the behaviour is unspecified
!$omp target update from(arrayA) to(arrayB)
do i = 1, 512
arrayA(i) = arrayB(i)
!$omp end parallel
!$omp target
- !WARNING: If TARGET DATA directive is nested inside TARGET region, the behaviour is unspecified
+ !PORTABILITY: If TARGET DATA directive is nested inside TARGET region, the behaviour is unspecified
!$omp target data map(to: a)
do i = 1, N
a = 3.14
allocate(B(N))
!$omp target
- !WARNING: If TARGET ENTER DATA directive is nested inside TARGET region, the behaviour is unspecified
+ !PORTABILITY: If TARGET ENTER DATA directive is nested inside TARGET region, the behaviour is unspecified
!$omp target enter data map(alloc:B)
!$omp end target
!$omp target
- !WARNING: If TARGET EXIT DATA directive is nested inside TARGET region, the behaviour is unspecified
+ !PORTABILITY: If TARGET EXIT DATA directive is nested inside TARGET region, the behaviour is unspecified
!$omp target exit data map(delete:B)
!$omp end target
deallocate(B)
! and C733, C734 and C779, C780, C782, C783, C784, and C785.
module m
- !WARNING: A derived type with the BIND attribute is empty
!ERROR: An ABSTRACT derived type must be extensible
+ !PORTABILITY: A derived type with the BIND attribute is empty
type, abstract, bind(c) :: badAbstract1
end type
!ERROR: An ABSTRACT derived type must be extensible
END DO
! REAL DO variable
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO rvar = 1, 10, 3
PRINT *, "rvar is: ", rvar
END DO
! DOUBLE PRECISISON DO variable
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO dvar = 1, 10, 3
PRINT *, "dvar is: ", dvar
END DO
! Pointer to REAL DO variable
ALLOCATE(prvar)
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO prvar = 1, 10, 3
PRINT *, "prvar is: ", prvar
END DO
! Pointer to DOUBLE PRECISION DO variable
ALLOCATE(pdvar)
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO pdvar = 1, 10, 3
PRINT *, "pdvar is: ", pdvar
END DO
END DO
! Shared association REAL DO variable
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO realvarshare = 1, 10, 3
PRINT *, "ivar is: ", ivar
END DO
! Shared association DOUBLE PRECISION DO variable
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO dpvarshare = 1, 10, 3
PRINT *, "ivar is: ", ivar
END DO
! Initial expressions
! REAL initial expression
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO ivar = rvar, 10, 3
PRINT *, "ivar is: ", ivar
END DO
! DOUBLE PRECISION initial expression
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO ivar = dvar, 10, 3
PRINT *, "ivar is: ", ivar
END DO
END DO
! Pointer to REAL initial expression
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO ivar = prvar, 10, 3
PRINT *, "ivar is: ", ivar
END DO
! Pointer to DOUBLE PRECISION initial expression
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO ivar = pdvar, 10, 3
PRINT *, "ivar is: ", ivar
END DO
! Final expression
! REAL final expression
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO ivar = 1, rvar, 3
PRINT *, "ivar is: ", ivar
END DO
! DOUBLE PRECISION final expression
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO ivar = 1, dvar, 3
PRINT *, "ivar is: ", ivar
END DO
END DO
! Pointer to REAL final expression
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO ivar = 1, prvar, 3
PRINT *, "ivar is: ", ivar
END DO
! Pointer to DOUBLE PRECISION final expression
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO ivar = pdvar, 10, 3
PRINT *, "ivar is: ", ivar
END DO
! Step expression
! REAL step expression
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO ivar = 1, 10, rvar
PRINT *, "ivar is: ", ivar
END DO
! DOUBLE PRECISION step expression
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO ivar = 1, 10, dvar
PRINT *, "ivar is: ", ivar
END DO
END DO
! Pointer to REAL step expression
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO ivar = 1, 10, prvar
PRINT *, "ivar is: ", ivar
END DO
! Pointer to DOUBLE PRECISION step expression
-!WARNING: DO controls should be INTEGER
+!PORTABILITY: DO controls should be INTEGER
DO ivar = 1, 10, pdvar
PRINT *, "ivar is: ", ivar
END DO
end forall
forall(i=1:10)
forall(j=1:10)
- !WARNING: FORALL index variable 'j' not used on left-hand side of assignment
!ERROR: Cannot redefine FORALL variable 'i'
+ !WARNING: FORALL index variable 'j' not used on left-hand side of assignment
i = 1
end forall
end forall
-! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
+! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic -Werror
write(*, '(B0)')
write(*, '(B3)')
-! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
-! Check that we get portability warnings for the extensions
+! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic -Werror
+! Check that we get portability warning for the extension:
! - exponent-letter 'Q'
-! - matching but non-'E' exponent letter together with kind-param
subroutine s
real :: realvar1 = 4.0
real :: realvar3 = 4.0_8
real :: realvar4 = 4.0E6_4
real :: realvar5 = 4.0E6_8
- !WARNING: nonstandard usage: Q exponent
+ !PORTABILITY: nonstandard usage: Q exponent
real :: realvar6 = 4.0Q6
- !WARNING: Explicit kind parameter together with non-'E' exponent letter is not standard
- real :: realvar7 = 4.0D6_8
- !WARNING: Explicit kind parameter on real constant disagrees with exponent letter 'd'
- real :: realvar8 = 4.0D6_4
end subroutine s
--- /dev/null
+! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic -Werror
+! Check that we get portability warning for the extension:
+! - matching but non-'E' exponent letter together with kind-param
+
+subroutine s
+ real :: realvar1 = 4.0
+ real :: realvar2 = 4.0D6
+ real :: realvar3 = 4.0_8
+ real :: realvar4 = 4.0E6_4
+ real :: realvar5 = 4.0E6_8
+ !PORTABILITY: Explicit kind parameter together with non-'E' exponent letter is not standard
+ real :: realvar6 = 4.0D6_8
+ !WARNING: Explicit kind parameter on real constant disagrees with exponent letter 'd'
+ real :: realvar7 = 4.0D6_4
+end subroutine s
-! RUN: %python %S/test_errors.py %s %flang_fc1
+! RUN: %python %S/test_errors.py %s %flang_fc1 -Werror
-!WARNING: aaaaaaaaaabbbbbbbbbbccccccccccddddddddddeeeeeeeeeeffffffffffggg1 has length 64, which is greater than the maximum name length 63
+!PORTABILITY: aaaaaaaaaabbbbbbbbbbccccccccccddddddddddeeeeeeeeeeffffffffffggg1 has length 64, which is greater than the maximum name length 63
program aaaaaaaaaabbbbbbbbbbccccccccccddddddddddeeeeeeeeeeffffffffffggg1
- !WARNING: aaaaaaaaaabbbbbbbbbbccccccccccddddddddddeeeeeeeeeeffffffffffggg2 has length 64, which is greater than the maximum name length 63
+ !PORTABILITY: aaaaaaaaaabbbbbbbbbbccccccccccddddddddddeeeeeeeeeeffffffffffggg2 has length 64, which is greater than the maximum name length 63
integer :: aaaaaaaaaabbbbbbbbbbccccccccccddddddddddeeeeeeeeeeffffffffffggg2
integer :: aaaaaaaaaabbbbbbbbbbccccccccccddddddddddeeeeeeeeeeffffffffffggg
- !WARNING: aaaaaaaaaabbbbbbbbbbccccccccccddddddddddeeeeeeeeeeffffffffffggg3 has length 64, which is greater than the maximum name length 63
+ !PORTABILITY: aaaaaaaaaabbbbbbbbbbccccccccccddddddddddeeeeeeeeeeffffffffffggg3 has length 64, which is greater than the maximum name length 63
call aaaaaaaaaabbbbbbbbbbccccccccccddddddddddeeeeeeeeeeffffffffffggg3
end
use :: m2, only: foo
!If we got the type of foo right, this declaration will fail
!due to an attempted division by zero.
+ !WARNING: INTEGER(4) division by zero
!ERROR: Must be a constant value
integer, parameter :: test = 1 / (kind(foo(1)) - kind(1.d0))
end subroutine
contains
real(kind=kind(x)) function foo(x)
real(kind=kind(1.0d0)) x
+ !WARNING: INTEGER(4) division by zero
!ERROR: Must be a constant value
integer, parameter :: test = 1 / (kind(foo) - kind(1.d0))
foo = n
character(len=l) :: v
!ERROR: Value of named constant 'o' (o) cannot be computed as a constant value
real, parameter :: o = o
+!WARNING: INTEGER(4) division by zero
!ERROR: Must be a constant value
integer, parameter :: p = 0/0
+!WARNING: INTEGER(4) division by zero
!ERROR: Must be a constant value
+!WARNING: INTEGER(4) division by zero
+!WARNING: INTEGER(4) division by zero
+!WARNING: INTEGER(4) division by zero
integer, parameter :: q = 1+2*(1/0)
integer not_constant
!ERROR: Must be a constant value
integer, parameter :: s1 = not_constant/2
!ERROR: Must be a constant value
integer, parameter :: s2 = 3/not_constant
+!WARNING: INTEGER(4) division by zero
!ERROR: Must be a constant value
integer(kind=2/0) r
integer, parameter :: sok(*)=[1,2]/[1,2]
+!WARNING: INTEGER(4) division by zero
!ERROR: Must be a constant value
integer, parameter :: snok(*)=[1,2]/[1,0]
end
enum, bind(C)
!ERROR: Enumerator value could not be computed from the given expression
+ !WARNING: INTEGER(4) division by zero
!ERROR: Must be a constant value
enumerator :: wrong = 0/0
end enum
# Cleans up the output from the compilation process to be easier to process
for line in log.split('\n'):
- m = re.search(r"[^:]*:(\d+:).*(?:error:)(.*)", line)
+ m = re.search(r"[^:]*:(\d+:).*(?:error|warning|portability|because):(.*)", line)
if m:
+ if re.search(r"warning: .*fold.*host", line):
+ continue # ignore host-dependent folding warnings
actual += m.expand(r"\1\2\n")
-# Gets the expected errors and their line number
+# Gets the expected errors and their line numbers
errors = []
for i, line in enumerate(src, 1):
- m = re.search(r"(?:^\s*!\s*ERROR: )(.*)", line)
+ m = re.search(r"(?:^\s*!\s*(?:ERROR|WARNING|PORTABILITY|BECAUSE): )(.*)", line)
if m:
errors.append(m.group(1))
continue
else:
print()
print("PASS")
-