]> git.ipfire.org Git - thirdparty/gcc.git/commitdiff
testsuite: Declare fortran array bound variables
authorMikael Morin <mikael@gcc.gnu.org>
Fri, 22 Mar 2024 11:32:17 +0000 (12:32 +0100)
committerMikael Morin <mikael@gcc.gnu.org>
Fri, 22 Mar 2024 12:07:38 +0000 (13:07 +0100)
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.

gcc/testsuite/gfortran.dg/graphite/pr107865.f90
gcc/testsuite/gfortran.dg/pr101267.f90
gcc/testsuite/gfortran.dg/pr112404.f90
gcc/testsuite/gfortran.dg/pr78061.f
gcc/testsuite/gfortran.dg/pr79315.f90
gcc/testsuite/gfortran.dg/vect/pr90681.f
gcc/testsuite/gfortran.dg/vect/pr97761.f90
gcc/testsuite/gfortran.dg/vect/pr99746.f90

index 6bddb17a1be57eb202599313f1f20c3df1e29150..323d8092ad256d34dbc8842c09f676706afcab2c 100644 (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)
index 12723cf9c221ed116faee02ebfc33c68f68ff275..99a6dcfa3425e01e1f08afc68dcba13eff927865 100644 (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
index 573fa28164a1205d8f88b67d084de1af5296fb45..4508bbc873893ddf2ed9696d5046727405ecafab 100644 (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
index 7e4dd3de8b5c331085b0ee0c505fa24be3cb9161..9061dea74daa559c50909ccf514c8b74df1aaf44 100644 (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
index 8cd89691ce9af992fee88067ee6940bb630f96b5..b754a2b32748366d975951a3b875f943a99cae90 100644 (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) ::                                          &
index 03d3987b146d6f3b47a658e781a8b4de2e4103d9..49f1d50ab8fdb62bf15debd7f62567015e8f1bae 100644 (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
index 250e2bf016e649cd28acc1d377526afcc7614782..401ef06e422bcded76feb9d832cca86f0a876ef7 100644 (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 
index fe947ae7ccfef2d0974cd4608e598aa871a26123..121d67d564de50aca68d5271c9b9fb5764749dd7 100644 (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, *)