[flang] Extend test_errors.py to test warnings and explanatory messages
authorPeter Klausler <pklausler@nvidia.com>
Fri, 21 Oct 2022 18:22:49 +0000 (11:22 -0700)
committerPeter Klausler <pklausler@nvidia.com>
Fri, 21 Oct 2022 19:44:08 +0000 (12:44 -0700)
flang/test/Semantics/test_errors,py only compares actual error messages
with expected error messages.  Many tests have expected warning messages
in them, but they are not checked.

A forthcoming change adds several new warning and explanatory messages
to the compiler, and these messages must be testable.

So (re-?) enable non-error message checking in test_errors.py and adjust some
existing tests to get them to pass.

Warning messages related to host-specific folding conditions will not
be emitted on all platforms, so they will continue to be ignored.

Differential Revision: https://reviews.llvm.org/D136479

13 files changed:
flang/test/Semantics/OpenMP/omp-copying.f90
flang/test/Semantics/OpenMP/omp-nested-target.f90
flang/test/Semantics/bindings01.f90
flang/test/Semantics/dosemantics03.f90
flang/test/Semantics/forall01.f90
flang/test/Semantics/io10.f90
flang/test/Semantics/kinds05.f90
flang/test/Semantics/kinds05b.f90 [new file with mode: 0644]
flang/test/Semantics/long-name.f90
flang/test/Semantics/resolve108.f90
flang/test/Semantics/resolve37.f90
flang/test/Semantics/resolve60.f90
flang/test/Semantics/test_errors.py

index 0095a09..f95227f 100644 (file)
@@ -1,4 +1,4 @@
-! 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
@@ -10,7 +10,7 @@
 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
@@ -20,7 +20,7 @@ end
 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()
@@ -33,7 +33,7 @@ subroutine copyin()
   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
@@ -44,7 +44,7 @@ subroutine copyprivate()
   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
index f23cb03..c130d80 100644 (file)
@@ -1,4 +1,4 @@
-! 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:
@@ -10,7 +10,7 @@ program main
   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)
@@ -20,7 +20,7 @@ program main
   !$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)
@@ -30,7 +30,7 @@ program main
   !$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
@@ -40,12 +40,12 @@ program main
 
   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)
index 27a6d57..0ab7f24 100644 (file)
@@ -3,8 +3,8 @@
 ! 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
index 89e46a6..a36c86b 100644 (file)
@@ -50,13 +50,13 @@ PROGRAM do_issue_458
   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
@@ -69,14 +69,14 @@ PROGRAM do_issue_458
 
 ! 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
@@ -148,26 +148,26 @@ PROGRAM do_issue_458
   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
@@ -178,13 +178,13 @@ PROGRAM do_issue_458
   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
@@ -221,13 +221,13 @@ PROGRAM do_issue_458
 
 ! 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
@@ -238,13 +238,13 @@ PROGRAM do_issue_458
   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
@@ -263,13 +263,13 @@ PROGRAM do_issue_458
 
 ! 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
@@ -280,13 +280,13 @@ PROGRAM do_issue_458
   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
index d90e529..5a493d4 100644 (file)
@@ -41,8 +41,8 @@ subroutine forall3
   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
index ef7008b..8104a10 100644 (file)
@@ -1,4 +1,4 @@
-! 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)')
index 3195339..90bd250 100644 (file)
@@ -1,7 +1,6 @@
-! 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
@@ -9,10 +8,6 @@ subroutine s
   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
diff --git a/flang/test/Semantics/kinds05b.f90 b/flang/test/Semantics/kinds05b.f90
new file mode 100644 (file)
index 0000000..3927829
--- /dev/null
@@ -0,0 +1,15 @@
+! 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
index 8576bf8..3dca0ab 100644 (file)
@@ -1,14 +1,14 @@
-! 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
index 6b687da..644b8fb 100644 (file)
@@ -44,6 +44,7 @@ subroutine s2
   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
@@ -53,6 +54,7 @@ module m3
  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
index bd94e12..f8229f1 100644 (file)
@@ -25,18 +25,25 @@ real :: u(l*2)
 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
index bf81db6..ff988d5 100644 (file)
@@ -32,6 +32,7 @@
 
   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
index 50f7a68..5a4d8b5 100755 (executable)
@@ -42,14 +42,16 @@ with tempfile.TemporaryDirectory() as tmpdir:
 
 # 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
@@ -72,4 +74,3 @@ if diffs != "":
 else:
     print()
     print("PASS")
-