]> git.ipfire.org Git - thirdparty/gcc.git/commitdiff
backport: [multiple changes]
authorDominique d'Humieres <dominiq@lps.ens.fr>
Sat, 24 May 2014 15:45:02 +0000 (17:45 +0200)
committerDominique d'Humieres <dominiq@gcc.gnu.org>
Sat, 24 May 2014 15:45:02 +0000 (17:45 +0200)
2014-05-24  Dominique d'Humieres <dominiq@lps.ens.fr>

Backport r195492 and r195815
2013-01-27  Paul Thomas  <pault@gcc.gnu.org>

PR fortran/55789
* gfortran.dg/associate_14.f90: New test.

PR fortran/56047
* gfortran.dg/associate_13.f90: New test.

2013-02-06  Paul Thomas <pault@gcc.gnu.org>

PR fortran/55789
* gfortran.dg/array_constructor_41.f90: New test.

From-SVN: r210894

gcc/testsuite/ChangeLog
gcc/testsuite/gfortran.dg/array_constructor_41.f90 [new file with mode: 0644]
gcc/testsuite/gfortran.dg/associate_13.f90 [new file with mode: 0644]
gcc/testsuite/gfortran.dg/associate_14.f90 [new file with mode: 0644]

index 665ff3a92120e40e2daa1e30fd25bc8371520419..0c5aced904e4f08815cbe73b0b45ee4920e22992 100644 (file)
@@ -1,3 +1,19 @@
+2014-05-24  Dominique d'Humieres <dominiq@lps.ens.fr>
+
+       Backport r195492 and r195815
+       2013-01-27  Paul Thomas  <pault@gcc.gnu.org>
+
+       PR fortran/55789                                                                
+       * gfortran.dg/associate_14.f90: New test.                                               
+
+       PR fortran/56047                                                                                
+       * gfortran.dg/associate_13.f90: New test.                                                               
+
+       2013-02-06  Paul Thomas <pault@gcc.gnu.org> 
+
+       PR fortran/55789
+       * gfortran.dg/array_constructor_41.f90: New test.
+
 2014-05-23  Richard Biener  <rguenther@suse.de>
 
        Backport from mainline
diff --git a/gcc/testsuite/gfortran.dg/array_constructor_41.f90 b/gcc/testsuite/gfortran.dg/array_constructor_41.f90
new file mode 100644 (file)
index 0000000..eb5fd92
--- /dev/null
@@ -0,0 +1,33 @@
+! { dg-do compile }
+! { dg-options "-fdump-tree-original" }
+! Test fix for PR55789
+!
+! Contributed by Joost VandVandole  <Joost.VandeVondele@mat.ethz.ch>
+!
+MODULE M1
+CONTAINS
+  SUBROUTINE cp_1d_i4_sort(arr)
+      INTEGER(kind=4), DIMENSION(:), &
+        INTENT(inout)                          :: arr
+      arr = (/ (i, i = 1, SIZE(arr)) /)
+  END SUBROUTINE
+END MODULE M1
+
+PROGRAM TEST
+  USE M1
+  INTEGER :: arr(1)
+  INTERFACE
+    SUBROUTINE mtrace() BIND(C,name="mtrace")
+    END SUBROUTINE
+  END INTERFACE
+  INTERFACE
+    SUBROUTINE muntrace() BIND(C,name="muntrace")
+    END SUBROUTINE
+  END INTERFACE
+  CALL mtrace()
+  CALL cp_1d_i4_sort(arr)
+  CALL muntrace()
+END
+
+! { dg-final { scan-tree-dump-times "realloc" 0 "original" } }
+! { dg-final { cleanup-tree-dump "original" } }
diff --git a/gcc/testsuite/gfortran.dg/associate_13.f90 b/gcc/testsuite/gfortran.dg/associate_13.f90
new file mode 100644 (file)
index 0000000..7c64d3f
--- /dev/null
@@ -0,0 +1,21 @@
+! { dg-do run }
+!
+! Tests the fix for PR56047.  This is actually a development of
+! the test case of comment #10.
+!
+! Reported by Juergen Reuter  <juergen.reuter@desy.de>
+!
+  implicit none
+  type :: process_variant_def_t
+    integer :: i
+  end type
+  type :: process_component_def_t
+     class(process_variant_def_t), allocatable :: variant_def
+  end type
+  type(process_component_def_t), dimension(1:2) :: initial
+  allocate (initial(1)%variant_def, source = process_variant_def_t (99))
+  associate (template => initial(1)%variant_def)
+    template%i = 77
+  end associate
+  if (initial(1)%variant_def%i .ne. 77) call abort
+end
diff --git a/gcc/testsuite/gfortran.dg/associate_14.f90 b/gcc/testsuite/gfortran.dg/associate_14.f90
new file mode 100644 (file)
index 0000000..765e365
--- /dev/null
@@ -0,0 +1,56 @@
+! { dg-do compile }
+! Tests the fix for PR55984.
+!
+! Contributed by Sylwester Arabas  <slayoo@staszic.waw.pl>
+!
+module bcd_m
+  type, abstract :: bcd_t
+    contains
+    procedure(bcd_fill_halos), deferred :: fill_halos
+  end type
+  abstract interface
+    subroutine bcd_fill_halos(this)
+      import :: bcd_t
+      class(bcd_t ) :: this
+    end subroutine
+  end interface
+end module
+
+module solver_m
+  use bcd_m
+  type, abstract :: solver_t
+    integer :: n, hlo
+    class(bcd_t), pointer :: bcx, bcy
+    contains
+    procedure(solver_advop), deferred :: advop
+  end type
+  abstract interface
+    subroutine solver_advop(this)
+      import solver_t
+      class(solver_t) :: this
+    end subroutine
+  end interface
+  contains
+end module
+
+module solver_mpdata_m
+  use solver_m
+  type :: mpdata_t
+    class(bcd_t), pointer :: bcx, bcy
+    contains
+    procedure :: advop => mpdata_advop
+  end type
+  contains
+  subroutine mpdata_advop(this)
+    class(mpdata_t) :: this
+    associate ( bcx => this%bcx, bcy => this%bcy )
+      call bcx%fill_halos()
+    end associate
+  end subroutine
+end module
+
+  use solver_mpdata_m
+  class(mpdata_t), allocatable :: that
+  call mpdata_advop (that)
+end
+