testsuite: Declare fortran array bound variables

This fixes invalid undeclared fortran array bound variables
in the testsuite.

gcc/testsuite/ChangeLog:

	* gfortran.dg/graphite/pr107865.f90: Declare array bound variable(s)
	as dummy argument(s).
	* gfortran.dg/pr101267.f90: Likewise.
	* gfortran.dg/pr112404.f90: Likewise.
	* gfortran.dg/pr78061.f: Likewise.
	* gfortran.dg/pr79315.f90: Likewise.
	* gfortran.dg/vect/pr90681.f: Likewise.
	* gfortran.dg/vect/pr97761.f90: Likewise.
	* gfortran.dg/vect/pr99746.f90: Likewise.
This commit is contained in:
Mikael Morin 2024-03-22 12:32:17 +01:00
parent 47de95d801
commit ebace32a26
8 changed files with 12 additions and 8 deletions

View file

@ -1,7 +1,7 @@
! { dg-do compile }
! { dg-options "-O1 -floop-parallelize-all -ftree-parallelize-loops=2" }
SUBROUTINE FNC (F)
SUBROUTINE FNC (F,N)
IMPLICIT REAL (A-H)
DIMENSION F(N)

View file

@ -1,7 +1,7 @@
! { dg-do compile }
! { dg-options "-Ofast" }
! { dg-additional-options "-march=znver2" { target x86_64-*-* i?86-*-* } }
SUBROUTINE sfddagd( regime, znt,ite ,jte )
SUBROUTINE sfddagd( regime, znt,ite ,jte, ime, IN )
REAL, DIMENSION( ime, IN) :: regime, znt
REAL, DIMENSION( ite, jte) :: wndcor_u
LOGICAL wrf_dm_on_monitor

View file

@ -1,7 +1,7 @@
! { dg-do compile }
! { dg-options "-Ofast" }
! { dg-additional-options "-mavx2" { target avx2 } }
SUBROUTINE sfddagd( regime, znt, ite, jte )
SUBROUTINE sfddagd( regime, znt, ite, jte, ime, IN )
REAL, DIMENSION( ime, IN) :: regime, znt
REAL, DIMENSION( ite, jte) :: wndcor_u
LOGICAL wrf_dm_on_monitor

View file

@ -1,6 +1,6 @@
! { dg-do compile }
! { dg-options "-O3 -fsplit-loops" }
SUBROUTINE SSYMM(C)
SUBROUTINE SSYMM(C,LDC)
REAL C(LDC,*)
LOGICAL LSAME
LOGICAL UPPER

View file

@ -10,7 +10,11 @@ SUBROUTINE wsm32D(t, &
its,&
ite, &
kts, &
kte &
kte, &
ims, &
ime, &
kms, &
kme &
)
REAL, DIMENSION( its:ite , kts:kte ), &
INTENT(INOUT) :: &

View file

@ -1,6 +1,6 @@
C { dg-do compile }
C { dg-additional-options "-march=armv8.2-a+sve" { target { aarch64*-*-* } } }
SUBROUTINE HMU (H1)
SUBROUTINE HMU (H1,NORBS)
COMMON DD(107)
DIMENSION H1(NORBS,*)
DO 70 J1 = IA,I1

View file

@ -1,7 +1,7 @@
! { dg-do compile }
! { dg-additional-options "-O1" }
subroutine ni (ps)
subroutine ni (ps, inout)
type vector
real x, y
end type

View file

@ -1,6 +1,6 @@
! { dg-do compile }
! { dg-additional-options "-march=armv8.3-a" { target aarch64-*-* } }
SUBROUTINE CLAREF(A, WANTZ, Z, ICOL1, ITMP1, ITMP2, T1, T2, V2)
SUBROUTINE CLAREF(A, WANTZ, Z, ICOL1, ITMP1, ITMP2, T1, T2, V2, LDA)
LOGICAL BLOCK, WANTZ
COMPLEX T1, T2, V2
COMPLEX A(LDA, *), VECS, Z(LDA, *)