public inbox for gcc-cvs@sourceware.org
help / color / mirror / Atom feed
* [gcc r13-7120] Fortran: Fix dg directives and remove trailing whitespaces in testsuite
@ 2023-04-08  6:49 Paul Thomas
  0 siblings, 0 replies; only message in thread
From: Paul Thomas @ 2023-04-08  6:49 UTC (permalink / raw)
  To: gcc-cvs

https://gcc.gnu.org/g:46fe32cb4d887d44a62f9c4ff2a72532d4eb5a19

commit r13-7120-g46fe32cb4d887d44a62f9c4ff2a72532d4eb5a19
Author: Paul Thomas <pault@gcc.gnu.org>
Date:   Sat Apr 8 07:49:13 2023 +0100

    Fortran: Fix dg directives and remove trailing whitespaces in testsuite
    
    2023-04-08   Paul Thomas  <pault@gcc.gnu.org>
    
            * gfortran.dg/c-interop/allocatable-optional-pointer.f90 : Fix
            dg directive and remove trailing whitespace.
            * gfortran.dg/c-interop/c407a-1.f90 : ditto
            * gfortran.dg/c-interop/c407b-1.f90 : ditto
            * gfortran.dg/c-interop/c407b-2.f90 : ditto
            * gfortran.dg/c-interop/c407c-1.f90 : ditto
            * gfortran.dg/c-interop/c535a-1.f90 : ditto
            * gfortran.dg/c-interop/c535a-2.f90 : ditto
            * gfortran.dg/c-interop/c535b-1.f90 : ditto
            * gfortran.dg/c-interop/c535b-2.f90 : ditto
            * gfortran.dg/c-interop/c535b-3.f90 : ditto
            * gfortran.dg/c-interop/c535c-1.f90 : ditto
            * gfortran.dg/c-interop/c535c-2.f90 : ditto
            * gfortran.dg/c-interop/deferred-character-1.f90 : ditto
            * gfortran.dg/c-interop/removed-restrictions-1.f90 : ditto
            * gfortran.dg/c-interop/removed-restrictions-2.f90 : ditto
            * gfortran.dg/c-interop/removed-restrictions-4.f90 : ditto
            * gfortran.dg/c-interop/tkr.f90 : ditto
            * gfortran.dg/class_result_10.f90 : ditto
            * gfortran.dg/dtio_35.f90 : ditto
            * gfortran.dg/gomp/affinity-clause-1.f90 : ditto
            * gfortran.dg/pr103258.f90 : ditto
            * gfortran.dg/pr59107.f90 : ditto
            * gfortran.dg/pr93835.f08 : ditto

Diff:
---
 .../c-interop/allocatable-optional-pointer.f90     |  6 ++--
 gcc/testsuite/gfortran.dg/c-interop/c407a-1.f90    |  6 ++--
 gcc/testsuite/gfortran.dg/c-interop/c407b-1.f90    |  6 ++--
 gcc/testsuite/gfortran.dg/c-interop/c407b-2.f90    | 32 +++++++++++-----------
 gcc/testsuite/gfortran.dg/c-interop/c407c-1.f90    |  2 +-
 gcc/testsuite/gfortran.dg/c-interop/c535a-1.f90    |  2 +-
 gcc/testsuite/gfortran.dg/c-interop/c535a-2.f90    |  6 ++--
 gcc/testsuite/gfortran.dg/c-interop/c535b-1.f90    |  6 ++--
 gcc/testsuite/gfortran.dg/c-interop/c535b-2.f90    | 18 ++++++------
 gcc/testsuite/gfortran.dg/c-interop/c535b-3.f90    |  4 +--
 gcc/testsuite/gfortran.dg/c-interop/c535c-1.f90    |  8 +++---
 gcc/testsuite/gfortran.dg/c-interop/c535c-2.f90    | 10 +++----
 .../gfortran.dg/c-interop/deferred-character-1.f90 |  4 +--
 .../c-interop/removed-restrictions-1.f90           |  4 +--
 .../c-interop/removed-restrictions-2.f90           |  4 +--
 .../c-interop/removed-restrictions-4.f90           |  4 +--
 gcc/testsuite/gfortran.dg/c-interop/tkr.f90        | 10 +++----
 gcc/testsuite/gfortran.dg/class_result_10.f90      |  2 +-
 gcc/testsuite/gfortran.dg/dtio_35.f90              |  2 +-
 .../gfortran.dg/gomp/affinity-clause-1.f90         |  2 +-
 gcc/testsuite/gfortran.dg/pr103258.f90             |  2 +-
 gcc/testsuite/gfortran.dg/pr59107.f90              |  2 +-
 gcc/testsuite/gfortran.dg/pr93835.f08              |  2 +-
 23 files changed, 72 insertions(+), 72 deletions(-)

diff --git a/gcc/testsuite/gfortran.dg/c-interop/allocatable-optional-pointer.f90 b/gcc/testsuite/gfortran.dg/c-interop/allocatable-optional-pointer.f90
index 5a785b8a94d..7d22eb3ac84 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/allocatable-optional-pointer.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/allocatable-optional-pointer.f90
@@ -1,9 +1,9 @@
-! { dg-do compile}
+! { dg-do compile }
 !
 ! TS 29113
 ! 5.3 ALLOCATABLE, OPTIONAL, and POINTER attributes
-! The ALLOCATABLE, OPTIONAL, and POINTER attributes may be specified 
-! for a dummy argument in a procedure interface that has the BIND 
+! The ALLOCATABLE, OPTIONAL, and POINTER attributes may be specified
+! for a dummy argument in a procedure interface that has the BIND
 ! attribute.
 
 subroutine test (a, b, c)
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c407a-1.f90 b/gcc/testsuite/gfortran.dg/c-interop/c407a-1.f90
index f239a1e8c43..86a20127511 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c407a-1.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c407a-1.f90
@@ -1,8 +1,8 @@
-! { dg-do compile}
+! { dg-do compile }
 !
 ! TS 29113
-! C407a An assumed-type entity shall be a dummy variable that does not 
-! have the ALLOCATABLE, CODIMENSION, INTENT(OUT), POINTER, or VALUE 
+! C407a An assumed-type entity shall be a dummy variable that does not
+! have the ALLOCATABLE, CODIMENSION, INTENT(OUT), POINTER, or VALUE
 ! attribute and is not an explicit-shape array.
 !
 ! This test file contains tests that are expected to all pass.
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c407b-1.f90 b/gcc/testsuite/gfortran.dg/c-interop/c407b-1.f90
index c9fc2b99647..a148afc5273 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c407b-1.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c407b-1.f90
@@ -1,15 +1,15 @@
-! { dg-do compile}
+! { dg-do compile }
 !
 ! TS 29113
 ! C407b  An assumed-type variable name shall not appear in a designator
 ! or expression except as an actual argument corresponding to a dummy
 ! argument that is assumed-type, or as the first argument to any of
-! the intrinsic and intrinsic module functions IS_CONTIGUOUS, LBOUND, 
+! the intrinsic and intrinsic module functions IS_CONTIGUOUS, LBOUND,
 ! PRESENT, RANK, SHAPE, SIZE, UBOUND, and C_LOC.
 !
 ! This test file contains tests that are expected to all pass.
 
-! Check that passing an assumed-type variable as an actual argument 
+! Check that passing an assumed-type variable as an actual argument
 ! corresponding to an assumed-type dummy works.
 
 module m
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c407b-2.f90 b/gcc/testsuite/gfortran.dg/c-interop/c407b-2.f90
index 49352fc9d71..90ae68fa7df 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c407b-2.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c407b-2.f90
@@ -1,16 +1,16 @@
 ! PR 101337
-! { dg-do compile}
+! { dg-do compile }
 !
 ! TS 29113
 ! C407b  An assumed-type variable name shall not appear in a designator
 ! or expression except as an actual argument corresponding to a dummy
 ! argument that is assumed-type, or as the first argument to any of
-! the intrinsic and intrinsic module functions IS_CONTIGUOUS, LBOUND, 
+! the intrinsic and intrinsic module functions IS_CONTIGUOUS, LBOUND,
 ! PRESENT, RANK, SHAPE, SIZE, UBOUND, and C_LOC.
 !
 ! This file contains tests that are expected to give diagnostics.
 
-! Check that passing an assumed-type variable as an actual argument 
+! Check that passing an assumed-type variable as an actual argument
 ! corresponding to a non-assumed-type dummy gives a diagnostic.
 
 module m
@@ -72,35 +72,35 @@ subroutine s2 (x, y)
     type is (integer)
       i = 0
     type is (real)
-      i = 1 
+      i = 1
     class default
       i = -1
   end select
 
   ! relational operations
   if (x & ! { dg-error "Assumed.type" "pr101337" }
-      .eq. y) then  ! { dg-error "Assumed.type" } 
+      .eq. y) then  ! { dg-error "Assumed.type" }
     return
   end if
   if (.not. (x & ! { dg-error "Assumed.type" "pr101337" }
-             .ne. y)) then  ! { dg-error "Assumed.type" } 
+             .ne. y)) then  ! { dg-error "Assumed.type" }
     return
   end if
-  if (.not. x) then  ! { dg-error "Assumed.type" } 
+  if (.not. x) then  ! { dg-error "Assumed.type" }
     return
   end if
 
   ! assignment
-  x &  ! { dg-error "Assumed.type" } 
-    = y  ! { dg-error "Assumed.type" } 
-  i = x  ! { dg-error "Assumed.type" } 
-  y = i  ! { dg-error "Assumed.type" } 
+  x &  ! { dg-error "Assumed.type" }
+    = y  ! { dg-error "Assumed.type" }
+  i = x  ! { dg-error "Assumed.type" }
+  y = i  ! { dg-error "Assumed.type" }
 
   ! arithmetic
-  i = x + 1  ! { dg-error "Assumed.type" } 
-  i = -y  ! { dg-error "Assumed.type" } 
+  i = x + 1  ! { dg-error "Assumed.type" }
+  i = -y  ! { dg-error "Assumed.type" }
   i = (x & ! { dg-error "Assumed.type" "pr101337" }
-       + y)  ! { dg-error "Assumed.type" } 
+       + y)  ! { dg-error "Assumed.type" }
 
   ! computed go to
   goto (10, 20, 30), x  ! { dg-error "Assumed.type|must be a scalar integer" }
@@ -116,7 +116,7 @@ subroutine s2 (x, y)
     continue
   end do
 
-end subroutine  
+end subroutine
 
 ! Check that calls to disallowed intrinsic functions produce a diagnostic.
 ! Again, this isn't exhaustive, there are just too many intrinsics and
@@ -147,4 +147,4 @@ subroutine s3 (x, y)
 
   i = kind (x)  ! { dg-error "Assumed.type" }
 
-end subroutine  
+end subroutine
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c407c-1.f90 b/gcc/testsuite/gfortran.dg/c-interop/c407c-1.f90
index 699f75f6142..7abe3382740 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c407c-1.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c407c-1.f90
@@ -1,5 +1,5 @@
 ! PR101333
-! { dg-do compile}
+! { dg-do compile }
 !
 ! TS 29113
 ! C407c An assumed-type actual argument that corresponds to an
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c535a-1.f90 b/gcc/testsuite/gfortran.dg/c-interop/c535a-1.f90
index 5550cf24005..f933808ff89 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c535a-1.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c535a-1.f90
@@ -1,4 +1,4 @@
-! { dg-do compile}
+! { dg-do compile }
 !
 ! TS 29113
 ! C535a  An assumed-rank entity shall be a dummy variable that does not
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c535a-2.f90 b/gcc/testsuite/gfortran.dg/c-interop/c535a-2.f90
index 026be4a5525..816e69124ce 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c535a-2.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c535a-2.f90
@@ -1,4 +1,4 @@
-! { dg-do compile}
+! { dg-do compile }
 ! { dg-additional-options "-fcoarray=single" }
 !
 ! TS 29113
@@ -43,7 +43,7 @@ subroutine s0 (a)
     integer, dimension(..) :: badblocklocal2  ! { dg-error "Assumed.rank" }
     integer :: badblocklocal3  ! { dg-error "Assumed.rank" }
     dimension badblocklocal3(..)
-  end block    
+  end block
 
 end subroutine
 
@@ -62,7 +62,7 @@ module m
     integer, dimension(..) :: badcomponent2  ! { dg-error "must have an explicit shape" }
   end type
 end module
-  
+
 ! Check that diagnostics are issued when dimension(..) is used in combination
 ! with the forbidden attributes.
 
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c535b-1.f90 b/gcc/testsuite/gfortran.dg/c-interop/c535b-1.f90
index 748e027f897..f8ecabe9a02 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c535b-1.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c535b-1.f90
@@ -1,9 +1,9 @@
-! { dg-do compile}
+! { dg-do compile }
 ! { dg-additional-options "-fcoarray=single" }
 !
 ! TS 29113
 ! C535b An assumed-rank variable name shall not appear in a designator
-! or expression except as an actual argument corresponding to a dummy 
+! or expression except as an actual argument corresponding to a dummy
 ! argument that is assumed-rank, the argument of the C_LOC function
 ! in the ISO_C_BINDING intrinsic module, or the first argument in a
 ! reference to an intrinsic inquiry function.
@@ -13,7 +13,7 @@
 !
 ! This test file contains tests that are expected to all pass.
 
-! Check that passing an assumed-rank variable as an actual argument 
+! Check that passing an assumed-rank variable as an actual argument
 ! corresponding to an assumed-rank dummy works.
 
 module m
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c535b-2.f90 b/gcc/testsuite/gfortran.dg/c-interop/c535b-2.f90
index 4d99f7fdb0e..caf61fe8270 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c535b-2.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c535b-2.f90
@@ -1,11 +1,11 @@
 ! PR 101334
 ! PR 101337
-! { dg-do compile}
+! { dg-do compile }
 ! { dg-additional-options "-fcoarray=single" }
 !
 ! TS 29113
 ! C535b An assumed-rank variable name shall not appear in a designator
-! or expression except as an actual argument corresponding to a dummy 
+! or expression except as an actual argument corresponding to a dummy
 ! argument that is assumed-rank, the argument of the C_LOC function
 ! in the ISO_C_BINDING intrinsic module, or the first argument in a
 ! reference to an intrinsic inquiry function.
@@ -16,7 +16,7 @@
 ! This test file contains tests that are expected to issue diagnostics
 ! for invalid code.
 
-! Check that passing an assumed-rank variable as an actual argument 
+! Check that passing an assumed-rank variable as an actual argument
 ! corresponding to a non-assumed-rank dummy gives a diagnostic.
 
 module m
@@ -57,7 +57,7 @@ subroutine test_calls (x, y)
   ! Make sure each invalid argument produces a diagnostic.
   ! scalar dummies
   call f (x, &  ! { dg-error "(A|a)ssumed.rank" }
-          y)  ! { dg-error "(A|a)ssumed.rank" "pr101337" } 
+          y)  ! { dg-error "(A|a)ssumed.rank" "pr101337" }
   ! assumed-rank dummies
   call g (x, y)  ! OK
   ! assumed-size dummies
@@ -295,15 +295,15 @@ subroutine test_expressions (a, b, c, l, m, n, x, y, z, p, q, r, s, i, j)
   n &  ! { dg-error "(A|a)ssumed.rank" }
     = j .neqv. m  ! { dg-error "(A|a)ssumed.rank" }
 
-end subroutine  
+end subroutine
 
 ! Check that calls to disallowed intrinsic functions produce a diagnostic.
 ! There are 100+ "elemental" intrinsics defined in the standard, and
 ! 25+ "transformational" intrinsics that accept array operands, and that
 ! doesn't include intrinsics in the standard modules.  To keep the length of
-! this test to something sane, check only a handful of these functions on 
-! the theory that related functions are probably implemented similarly and 
-! probably share the same argument-processing code.  
+! this test to something sane, check only a handful of these functions on
+! the theory that related functions are probably implemented similarly and
+! probably share the same argument-processing code.
 
 subroutine test_intrinsics (i1, i2, r1, r2, c1, c2, l1, l2, s1, s2)
   implicit none
@@ -331,7 +331,7 @@ subroutine test_intrinsics (i1, i2, r1, r2, c1, c2, l1, l2, s1, s2)
     = exp (r2)  ! { dg-error "(A|a)ssumed.rank" }
   r1 &  ! { dg-error "(A|a)ssumed.rank" }
     = sinh (r2)  ! { dg-error "(A|a)ssumed.rank" }
-  
+
   ! bit operations
   l1 &  ! { dg-error "(A|a)ssumed.rank" }
     = blt (i1, &  ! { dg-error "(A|a)ssumed.rank" }
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c535b-3.f90 b/gcc/testsuite/gfortran.dg/c-interop/c535b-3.f90
index 23862e54d74..e882fbcfd2f 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c535b-3.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c535b-3.f90
@@ -1,10 +1,10 @@
 ! PR 101334
-! { dg-do compile}
+! { dg-do compile }
 ! { dg-additional-options "-fcoarray=single" }
 !
 ! TS 29113
 ! C535b An assumed-rank variable name shall not appear in a designator
-! or expression except as an actual argument corresponding to a dummy 
+! or expression except as an actual argument corresponding to a dummy
 ! argument that is assumed-rank, the argument of the C_LOC function
 ! in the ISO_C_BINDING intrinsic module, or the first argument in a
 ! reference to an intrinsic inquiry function.
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c535c-1.f90 b/gcc/testsuite/gfortran.dg/c-interop/c535c-1.f90
index 2158c35be82..8f0cff111db 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c535c-1.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c535c-1.f90
@@ -1,9 +1,9 @@
 ! PR 54753
-! { dg-do compile}
+! { dg-do compile }
 !
 ! TS 29113
 ! C535c If an assumed-size or nonallocatable nonpointer assumed-rank
-! array is an actual argument corresponding to a dummy argument that 
+! array is an actual argument corresponding to a dummy argument that
 ! is an INTENT(OUT) assumed-rank array, it shall not be polymorphic, [...].
 !
 ! This constraint is numbered C839 in the Fortran 2018 standard.
@@ -16,7 +16,7 @@ module t
     integer :: id
     real :: xyz(3)
   end type
-end module  
+end module
 
 module m
   use t
@@ -74,7 +74,7 @@ contains
     class(*) :: a1, a2
     call upoly (a1, a2)
   end subroutine
-  
+
   ! The polymorphic cases for assumed-size are bad.
   subroutine test_assumed_size_nonpolymorphic (a1, a2)
     type(t1) :: a1(*), a2(*)
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c535c-2.f90 b/gcc/testsuite/gfortran.dg/c-interop/c535c-2.f90
index f232efae9fc..5e89f57640c 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c535c-2.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c535c-2.f90
@@ -1,10 +1,10 @@
 ! PR 54753
-! { dg-do compile}
+! { dg-do compile }
 !
 ! TS 29113
 ! C535c If an assumed-size or nonallocatable nonpointer assumed-rank
-! array is an actual argument corresponding to a dummy argument that 
-! is an INTENT(OUT) assumed-rank array, it shall not be [...] 
+! array is an actual argument corresponding to a dummy argument that
+! is an INTENT(OUT) assumed-rank array, it shall not be [...]
 ! finalizable [...].
 !
 ! This constraint is numbered C839 in the Fortran 2018 standard.
@@ -44,7 +44,7 @@ contains
   ! Calls with an assumed-size array argument should be rejected.
   subroutine test_assumed_size (a1, a2)
     type(t1) :: a1(*), a2(*)
-    
+
     call s1 (a1, a2)  !  { dg-error "(A|a)ssumed.rank" }
   end subroutine
 
@@ -61,7 +61,7 @@ contains
 
     call s1 (a1, a2)
   end subroutine
-  
+
   ! The call should be rejected with a nonallocatable nonpointer
   ! assumed-rank actual argument.
   subroutine test_assumed_rank_plain (a1, a2)
diff --git a/gcc/testsuite/gfortran.dg/c-interop/deferred-character-1.f90 b/gcc/testsuite/gfortran.dg/c-interop/deferred-character-1.f90
index 3c3c2574101..6a26fd0eea3 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/deferred-character-1.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/deferred-character-1.f90
@@ -1,9 +1,9 @@
 ! PR92482
-! { dg-do compile}
+! { dg-do compile }
 !
 ! TS 29113
 ! 8.7 Interoperability of procedures and procedure interfaces
-! 
+!
 ! If a dummy argument in an interoperable interface is of type
 ! CHARACTER and is allocatable or a pointer, its character length shall
 ! be deferred.
diff --git a/gcc/testsuite/gfortran.dg/c-interop/removed-restrictions-1.f90 b/gcc/testsuite/gfortran.dg/c-interop/removed-restrictions-1.f90
index d2155ec6eeb..250c3970b0e 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/removed-restrictions-1.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/removed-restrictions-1.f90
@@ -1,8 +1,8 @@
-! { dg-do compile}
+! { dg-do compile }
 !
 ! TS 29113
 ! 8.1 Removed restrictions on ISO_C_BINDING module procedures
-! 
+!
 ! The subroutine C_F_POINTER from the intrinsic module ISO_C_BINDING has
 ! the restriction in ISO/IEC 1539- 1:2010 that if FPTR is an array, it
 ! shall be of interoperable type.
diff --git a/gcc/testsuite/gfortran.dg/c-interop/removed-restrictions-2.f90 b/gcc/testsuite/gfortran.dg/c-interop/removed-restrictions-2.f90
index 3c49de37152..eb0c970eb53 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/removed-restrictions-2.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/removed-restrictions-2.f90
@@ -1,8 +1,8 @@
-! { dg-do compile}
+! { dg-do compile }
 !
 ! TS 29113
 ! 8.1 Removed restrictions on ISO_C_BINDING module procedures
-! 
+!
 ! The function C_F_PROCPOINTER from the intrinsic module ISO_C_BINDING
 ! has the restriction in ISO/IEC 1539-1:2010 that CPTR and FPTR shall
 ! not be the C address and interface of a noninteroperable Fortran
diff --git a/gcc/testsuite/gfortran.dg/c-interop/removed-restrictions-4.f90 b/gcc/testsuite/gfortran.dg/c-interop/removed-restrictions-4.f90
index b44defd40e1..a5827235341 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/removed-restrictions-4.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/removed-restrictions-4.f90
@@ -1,8 +1,8 @@
-! { dg-do compile}
+! { dg-do compile }
 !
 ! TS 29113
 ! 8.1 Removed restrictions on ISO_C_BINDING module procedures
-! 
+!
 ! [...]
 !
 ! The function C_FUNLOC from the intrinsic module ISO_C_BINDING has
diff --git a/gcc/testsuite/gfortran.dg/c-interop/tkr.f90 b/gcc/testsuite/gfortran.dg/c-interop/tkr.f90
index c0c0d7e86f8..9ba7f95937a 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/tkr.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/tkr.f90
@@ -1,12 +1,12 @@
-! { dg-do compile}
+! { dg-do compile }
 !
 ! TS 29113
-! The definition of TKR compatible in paragraph 2 of subclause 12.4.3.4.5 
+! The definition of TKR compatible in paragraph 2 of subclause 12.4.3.4.5
 ! of ISO/IEC 1539-1:2010 is changed to:
 !
-! A dummy argument is type, kind, and rank compatible, or TKR compatible, 
-! with another dummy argument if the first is type compatible with the 
-! second, the kind type parameters of the first have the same values as 
+! A dummy argument is type, kind, and rank compatible, or TKR compatible,
+! with another dummy argument if the first is type compatible with the
+! second, the kind type parameters of the first have the same values as
 ! the corresponding kind type parameters of the second, and both have the
 ! same rank or either is assumed-rank.
 !
diff --git a/gcc/testsuite/gfortran.dg/class_result_10.f90 b/gcc/testsuite/gfortran.dg/class_result_10.f90
index a4d29ab9c1d..acfb7c35cfb 100644
--- a/gcc/testsuite/gfortran.dg/class_result_10.f90
+++ b/gcc/testsuite/gfortran.dg/class_result_10.f90
@@ -1,4 +1,4 @@
-! { dg-do run}
+! { dg-do run }
 
 
 ! PR fortran/99585
diff --git a/gcc/testsuite/gfortran.dg/dtio_35.f90 b/gcc/testsuite/gfortran.dg/dtio_35.f90
index d7211df87ac..c56fa011655 100644
--- a/gcc/testsuite/gfortran.dg/dtio_35.f90
+++ b/gcc/testsuite/gfortran.dg/dtio_35.f90
@@ -1,4 +1,4 @@
-! { dg-compile }
+! { dg-do compile }
 !
 ! Reported by Vladimir Nikishkin
 ! at https://stackoverflow.com/questions/60972134/whats-wrong-with-the-following-fortran-code-gfortran-dtio-dummy-argument-at#
diff --git a/gcc/testsuite/gfortran.dg/gomp/affinity-clause-1.f90 b/gcc/testsuite/gfortran.dg/gomp/affinity-clause-1.f90
index 08c7740cf0d..b8c7b5d68ad 100644
--- a/gcc/testsuite/gfortran.dg/gomp/affinity-clause-1.f90
+++ b/gcc/testsuite/gfortran.dg/gomp/affinity-clause-1.f90
@@ -24,7 +24,7 @@ end
 
 ! { dg-final { scan-tree-dump-times "#pragma omp task affinity\\(iterator\\(integer\\(kind=4\\) jj=2:5:2, integer\\(kind=4\\) i=D\\.\[0-9\]+:5:1\\):b\\\[.* <?i>? \\+ -1\\\]\\) affinity\\(iterator\\(integer\\(kind=4\\) jj=2:5:2, integer\\(kind=4\\) i=D\\.\[0-9\]+:5:1\\):d\\\[\\(.*jj \\* 5 \\+ .* <?i>?\\) \\+ -6\\\]\\)" 1 "original" } }
 
-! { dg final { scan-tree-dump-times "#pragma omp task affinity\\(iterator\\(integer\\(kind=4\\) i=D\\.\[0-9\]+:5:1\\):b\\\[\\(.* <?i>? \\+ -1\\\]\\) affinity\\(iterator\\(integer\\(kind=4\\) i=D\\.\[0-9\]+:5:1\\):d\\\[\\(\\(integer\\(kind=8\\)\\) i \\+ -1\\) \\* 6\\\]\\)"  1 "original" } }
+! { dg-final { scan-tree-dump-times "#pragma omp task affinity\\(iterator\\(integer\\(kind=4\\) i=D\\.\[0-9\]+:5:1\\):b\\\[\\(.* <?i>? \\+ -1\\\]\\) affinity\\(iterator\\(integer\\(kind=4\\) i=D\\.\[0-9\]+:5:1\\):d\\\[\\(\\(integer\\(kind=8\\)\\) i \\+ -1\\) \\* 6\\\]\\)"  1 "original" } }
 
 ! { dg-final { scan-tree-dump-times "#pragma omp task affinity\\(iterator\\(integer\\(kind=4\\) i=1:5:1\\):a\\)\[^ \]" 1 "original" } }
 
diff --git a/gcc/testsuite/gfortran.dg/pr103258.f90 b/gcc/testsuite/gfortran.dg/pr103258.f90
index 4521fcd69c1..4a3bb6fc2e7 100644
--- a/gcc/testsuite/gfortran.dg/pr103258.f90
+++ b/gcc/testsuite/gfortran.dg/pr103258.f90
@@ -1,4 +1,4 @@
-! { dg-do compile}
+! { dg-do compile }
 ! { dg-additional-options "-Wno-pedantic" }
 !
 ! Test from PR103258.  This used to ICE due to incorrectly marking the
diff --git a/gcc/testsuite/gfortran.dg/pr59107.f90 b/gcc/testsuite/gfortran.dg/pr59107.f90
index a84328f0851..969154a1537 100644
--- a/gcc/testsuite/gfortran.dg/pr59107.f90
+++ b/gcc/testsuite/gfortran.dg/pr59107.f90
@@ -1,4 +1,4 @@
-! { dg-compile }
+! { dg-do compile }
 ! { dg-options "-Wsurprising" }
 
 ! There should be no surprising warnings
diff --git a/gcc/testsuite/gfortran.dg/pr93835.f08 b/gcc/testsuite/gfortran.dg/pr93835.f08
index 933e249e632..2fa1585604b 100644
--- a/gcc/testsuite/gfortran.dg/pr93835.f08
+++ b/gcc/testsuite/gfortran.dg/pr93835.f08
@@ -1,4 +1,4 @@
-! {dg-do run }
+! { dg-do run }
 !
 ! PR fortran/93835 - the following code resulted in an ICE
 !

^ permalink raw reply	[flat|nested] only message in thread

only message in thread, other threads:[~2023-04-08  6:49 UTC | newest]

Thread overview: (only message) (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2023-04-08  6:49 [gcc r13-7120] Fortran: Fix dg directives and remove trailing whitespaces in testsuite Paul Thomas

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).