public inbox for fortran@gcc.gnu.org
 help / color / mirror / Atom feed
From: Paul Richard Thomas <paul.richard.thomas@gmail.com>
To: Manfred Schwarb <manfred99@gmx.ch>
Cc: gcc-patches <gcc-patches@gcc.gnu.org>,
	"fortran@gcc.gnu.org" <fortran@gcc.gnu.org>
Subject: Re: [Patch, fortran] PR87477 - [meta-bug] [F03] issues concerning the ASSOCIATE statement
Date: Fri, 7 Apr 2023 08:02:02 +0100	[thread overview]
Message-ID: <CAGkQGi+wByOR0owHMzMyAjb9KUMENkf=_Z-p23KgxC8OUoWy+A@mail.gmail.com> (raw)
In-Reply-To: <CAGkQGiLhghHgQOwE8QG+VBMV6qyWTeDr_=7H6XM77Pruyw_K4w@mail.gmail.com>


[-- Attachment #1.1: Type: text/plain, Size: 6979 bytes --]

Hi All,

Please find attached the patch to fix the dg directives and remove a lot of
trailing white space.

Unless there are any objections, I will commit as obvious over the weekend.

Cheers

Paul

Fortran: Fix dg directives and remove trailing whitespaces in testsuite

2023-04-07  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/goacc/array-with-dt-2.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



On Wed, 29 Mar 2023 at 09:53, Paul Richard Thomas <
paul.richard.thomas@gmail.com> wrote:

> Hi Manfred,
>
> Indeed I do :-) Thanks for the spot. I have decided that it will be less
> messy if I roll all the testcases into one or, perhaps two =>
> associate_xx.f90
>
> Forgetting the space before the final brace seems to be rife!
>
> Cheers
>
> Paul
>
>
> On Wed, 29 Mar 2023 at 09:24, Manfred Schwarb <manfred99@gmx.ch> wrote:
>
>> Am 28.03.23 um 23:04 schrieb Paul Richard Thomas via Fortran:
>> > Hi All,
>> >
>> > I have made a start on ASSOCIATE issues. Some of the low(-ish) hanging
>> > fruit are already fixed but I have yet to check that they a really fixed
>> > and to close them:
>> > pr102106, pr102111, pr104430, pr106048, pr85510, pr87460, pr92960 &
>> pr93338
>> >
>> > The attached patch picks up those PRs involving deferred length
>> characters
>> > in one guise or another. I believe that it is all pretty
>> straightforward.
>> > Structure constructors with allocatable, deferred length, character
>> array
>> > components just weren't implemented and so this is the biggest part of
>> the
>> > patch. I found two other, non-associate PRs(106918 &  105205) that are
>> > fixed and there are probably more.
>> >
>> > The chunk in trans-io.cc is something of a kludge, which I will come
>> back
>> > to. Some descriptors come through with a data pointer that looks as if
>> it
>> > should be OK but
>> >
>> > I thought to submit this now to get it out of the way. The ratio of PRs
>> > fixed to the size of the patch warrants this. The next stage is going
>> to be
>> > rather messy and so "I might take a little while" (cross talk between
>> > associate and select type, in particular).
>> >
>> > Regtests OK - good for mainline?
>> >
>>
>> Paul, you have some "dg-do-run" and "dg-do-compile" statements in your
>> testcases,
>> could you change them into their single-minus-sign variants?
>>
>> Cheers,
>> Manfred
>>
>>
>> BTW: I just ran my script again and found the following testsuite issues
>> (note that outer-most
>> braces need to be space-padded):
>>
>> ./c-interop/removed-restrictions-1.f90:! { dg-do compile}
>> ./c-interop/removed-restrictions-2.f90:! { dg-do compile}
>> ./c-interop/removed-restrictions-3.f90:! { dg-do compile}
>> ./c-interop/removed-restrictions-4.f90:! { dg-do compile}
>> ./c-interop/tkr.f90:! { dg-do compile}
>> ./c-interop/c407c-1.f90:! { dg-do compile}
>> ./c-interop/deferred-character-1.f90:! { dg-do compile}
>> ./c-interop/allocatable-optional-pointer.f90:! { dg-do compile}
>> ./c-interop/c407a-1.f90:! { dg-do compile}
>> ./c-interop/c407b-1.f90:! { dg-do compile}
>> ./c-interop/c407b-2.f90:! { dg-do compile}
>> ./c-interop/c535a-1.f90:! { dg-do compile}
>> ./c-interop/c535a-2.f90:! { dg-do compile}
>> ./c-interop/c535b-1.f90:! { dg-do compile}
>> ./c-interop/c535b-2.f90:! { dg-do compile}
>> ./c-interop/c535b-3.f90:! { dg-do compile}
>> ./c-interop/c535c-1.f90:! { dg-do compile}
>> ./c-interop/c535c-2.f90:! { dg-do compile}
>> ./gomp/affinity-clause-1.f90:! { 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" } }
>> ./class_result_10.f90:! { dg-do run}
>> ./pr103258.f90:! { dg-do compile}
>> ./dtio_35.f90:! { dg-compile }
>> ./pr93835.f08:! {dg-do run }
>> ./pr59107.f90:! { dg-compile }
>>
>>
>>
>> > Cheers
>> >
>> > Paul
>> >
>> > Fortran: Fix some of the bugs in associate [PR87477]
>> >
>> > 2023-03-28  Paul Thomas  <pault@gcc.gnu.org>
>> >
>> > gcc/fortran
>> > PR fortran/87477
>> > * trans-array.cc (gfc_conv_expr_descriptor): Guard string len
>> > expression in condition.
>> > (duplicate_allocatable): Make element type more explicit with
>> > 'eltype'.
>> > * trans-expr.cc (gfc_get_expr_charlen): Retain last charlen in
>> > 'previous' and use if end expression in substring reference is
>> > null.
>> > (gfc_conv_string_length): Use gfc_conv_expr_descriptor if
>> > 'expr_flat' is an array.
>> > (gfc_trans_alloc_subarray_assign): If this is a deferred string
>> > length component, store the string length in the hidden comp.
>> > Update the typespec length accordingly. Generate a new type
>> > spec for the call to gfc_duplicate-allocatable in this case.
>> > * trans-io.cc (gfc_trans_transfer): Scalarize transfer of
>> > deferred character array components.
>> >
>> >
>> > gcc/testsuite/
>> > PR fortran/92994
>> > * gfortran.dg/finalize_51.f90 : Update an error message.
>> >
>> > PR fortran/85686
>> > * gfortran.dg/pr85686.f90 : New test
>> >
>> > PR fortran/88247
>> > * gfortran.dg/pr88247.f90 : New test
>> >
>> > PR fortran/91941
>> > * gfortran.dg/pr91941.f90 : New test
>> >
>> > PR fortran/92779
>> > * gfortran.dg/pr92779.f90 : New test
>> >
>> > PR fortran/93339
>> > * gfortran.dg/pr93339.f90 : New test
>> >
>> > PR fortran/93813
>> > * gfortran.dg/pr93813.f90 : New test
>> >
>> > PR fortran/100948
>> > * gfortran.dg/pr100948.f90 : New test
>> >
>> > PR fortran/102106
>> > * gfortran.dg/pr102106.f90 : New test
>> >
>> > PR fortran/105205
>> > * gfortran.dg/pr105205.f90 : New test
>> >
>> > PR fortran/106918
>> > * gfortran.dg/pr106918.f90 : New test
>>
>>
>
> --
> "If you can't explain it simply, you don't understand it well enough" -
> Albert Einstein
>


-- 
"If you can't explain it simply, you don't understand it well enough" -
Albert Einstein

[-- Attachment #2: dg-fix.diff --]
[-- Type: text/x-patch, Size: 21690 bytes --]

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/goacc/array-with-dt-2.f90 b/gcc/testsuite/gfortran.dg/goacc/array-with-dt-2.f90
index 58f4ce84a2c..560e5351323 100644
--- a/gcc/testsuite/gfortran.dg/goacc/array-with-dt-2.f90
+++ b/gcc/testsuite/gfortran.dg/goacc/array-with-dt-2.f90
@@ -8,8 +8,9 @@ type(t), allocatable :: b(:)
 ! { dg-note {'b' declared here} {} { target *-*-* } .-1 }

 !$acc update host(b(::2))
-! { dg-warning {'b\.dim\[0\]\.ubound' is used uninitialized} {} { target *-*-* } .-1 }
-! { dg-warning {'b\.dim\[0\]\.lbound' is used uninitialized} {} { target *-*-* } .-2 }
+! { dg-warning {'b\.span' is used uninitialized} {} { target *-*-* } .-1 }
+! { dg-warning {'b\.dim\[0\]\.ubound' is used uninitialized} {} { target *-*-* } .-2 }
+! { dg-warning {'b\.dim\[0\]\.lbound' is used uninitialized} {} { target *-*-* } .-3 }
 !$acc update host(b(1)%A(::3,::4))
 end

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
 !

  reply	other threads:[~2023-04-07  7:02 UTC|newest]

Thread overview: 16+ messages / expand[flat|nested]  mbox.gz  Atom feed  top
2023-03-28 21:04 Paul Richard Thomas
2023-03-29  8:24 ` Manfred Schwarb
2023-03-29  8:53   ` Paul Richard Thomas
2023-04-07  7:02     ` Paul Richard Thomas [this message]
2023-04-07  9:40       ` Harald Anlauf
2023-04-07  7:07 ` Ping! " Paul Richard Thomas
2023-04-07  9:41   ` Harald Anlauf
2023-04-07  9:41     ` Harald Anlauf
2023-04-07 13:53     ` Paul Richard Thomas
2023-04-07 19:28       ` Harald Anlauf
2023-04-07 21:35         ` Paul Richard Thomas
2023-04-07 21:38           ` Paul Richard Thomas
2023-04-08 13:56           ` Harald Anlauf
2023-06-01 15:20 Paul Richard Thomas
2023-06-01 17:58 ` Mikael Morin
2023-06-02  7:46   ` Paul Richard Thomas

Reply instructions:

You may reply publicly to this message via plain-text email
using any one of the following methods:

* Save the following mbox file, import it into your mail client,
  and reply-to-all from there: mbox

  Avoid top-posting and favor interleaved quoting:
  https://en.wikipedia.org/wiki/Posting_style#Interleaved_style

* Reply using the --to, --cc, and --in-reply-to
  switches of git-send-email(1):

  git send-email \
    --in-reply-to='CAGkQGi+wByOR0owHMzMyAjb9KUMENkf=_Z-p23KgxC8OUoWy+A@mail.gmail.com' \
    --to=paul.richard.thomas@gmail.com \
    --cc=fortran@gcc.gnu.org \
    --cc=gcc-patches@gcc.gnu.org \
    --cc=manfred99@gmx.ch \
    /path/to/YOUR_REPLY

  https://kernel.org/pub/software/scm/git/docs/git-send-email.html

* If your mail client supports setting the In-Reply-To header
  via mailto: links, try the mailto: link
Be sure your reply has a Subject: header at the top and a blank line before the message body.
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).