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
This commit is contained in:
parent
d8ec34a162
commit
46fe32cb4d
23 changed files with 72 additions and 72 deletions
|
@ -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)
|
||||
|
|
|
@ -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.
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -1,5 +1,5 @@
|
|||
! PR101333
|
||||
! { dg-do compile}
|
||||
! { dg-do compile }
|
||||
!
|
||||
! TS 29113
|
||||
! C407c An assumed-type actual argument that corresponds to an
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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.
|
||||
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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" }
|
||||
|
|
|
@ -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.
|
||||
|
|
|
@ -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(*)
|
||||
|
|
|
@ -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)
|
||||
|
|
|
@ -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.
|
||||
|
|
|
@ -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.
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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.
|
||||
!
|
||||
|
|
|
@ -1,4 +1,4 @@
|
|||
! { dg-do run}
|
||||
! { dg-do run }
|
||||
|
||||
|
||||
! PR fortran/99585
|
||||
|
|
|
@ -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#
|
||||
|
|
|
@ -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" } }
|
||||
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -1,4 +1,4 @@
|
|||
! { dg-compile }
|
||||
! { dg-do compile }
|
||||
! { dg-options "-Wsurprising" }
|
||||
|
||||
! There should be no surprising warnings
|
||||
|
|
|
@ -1,4 +1,4 @@
|
|||
! {dg-do run }
|
||||
! { dg-do run }
|
||||
!
|
||||
! PR fortran/93835 - the following code resulted in an ICE
|
||||
!
|
||||
|
|
Loading…
Add table
Reference in a new issue