aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.8/gcc/testsuite/gfortran.dg/assumed_rank_10.f90
diff options
context:
space:
mode:
authorBen Cheng <bccheng@google.com>2013-03-28 11:14:20 -0700
committerBen Cheng <bccheng@google.com>2013-03-28 12:40:33 -0700
commitaf0c51ac87ab2a87caa03fa108f0d164987a2764 (patch)
tree4b8b470f7c5b69642fdab8d0aa1fbc148d02196b /gcc-4.8/gcc/testsuite/gfortran.dg/assumed_rank_10.f90
parentd87cae247d39ebf4f5a6bf25c932a14d2fdb9384 (diff)
downloadtoolchain_gcc-af0c51ac87ab2a87caa03fa108f0d164987a2764.tar.gz
toolchain_gcc-af0c51ac87ab2a87caa03fa108f0d164987a2764.tar.bz2
toolchain_gcc-af0c51ac87ab2a87caa03fa108f0d164987a2764.zip
[GCC 4.8] Initial check-in of GCC 4.8.0
Change-Id: I0719d8a6d0f69b367a6ab6f10eb75622dbf12771
Diffstat (limited to 'gcc-4.8/gcc/testsuite/gfortran.dg/assumed_rank_10.f90')
-rw-r--r--gcc-4.8/gcc/testsuite/gfortran.dg/assumed_rank_10.f90106
1 files changed, 106 insertions, 0 deletions
diff --git a/gcc-4.8/gcc/testsuite/gfortran.dg/assumed_rank_10.f90 b/gcc-4.8/gcc/testsuite/gfortran.dg/assumed_rank_10.f90
new file mode 100644
index 000000000..ac2828394
--- /dev/null
+++ b/gcc-4.8/gcc/testsuite/gfortran.dg/assumed_rank_10.f90
@@ -0,0 +1,106 @@
+! { dg-do run }
+! { dg-options "-fdump-tree-original" }
+!
+! PR fortran/48820
+!
+! Ensure that the value of scalars to assumed-rank arrays is
+! copied back, if and only its pointer address could have changed.
+!
+program test
+ implicit none
+ type t
+ integer :: aa
+ end type t
+
+ integer, allocatable :: iia
+ integer, pointer :: iip
+
+ type(t), allocatable :: jja
+ type(t), pointer :: jjp
+
+ logical :: is_present
+
+ is_present = .true.
+
+ allocate (iip, jjp)
+
+ iia = 7
+ iip = 7
+ jja = t(88)
+ jjp = t(88)
+
+ call faa(iia, jja) ! Copy back
+ if (iia /= 7 .and. jja%aa /= 88) call abort ()
+ call fai(iia, jja) ! No copy back
+ if (iia /= 7 .and. jja%aa /= 88) call abort ()
+
+ call fpa(iip, jjp) ! Copy back
+ if (iip /= 7 .and. jjp%aa /= 88) call abort ()
+ call fpi(iip, jjp) ! No copy back
+ if (iip /= 7 .and. jjp%aa /= 88) call abort ()
+
+ call fnn(iia, jja) ! No copy back
+ if (iia /= 7 .and. jja%aa /= 88) call abort ()
+ call fno(iia, jja) ! No copy back
+ if (iia /= 7 .and. jja%aa /= 88) call abort ()
+ call fnn(iip, jjp) ! No copy back
+ if (iip /= 7 .and. jjp%aa /= 88) call abort ()
+ call fno(iip, jjp) ! No copy back
+ if (iip /= 7 .and. jjp%aa /= 88) call abort ()
+
+ is_present = .false.
+
+ call fpa(null(), null()) ! No copy back
+ call fpi(null(), null()) ! No copy back
+ call fno(null(), null()) ! No copy back
+
+ call fno() ! No copy back
+
+contains
+
+ subroutine faa (xx1, yy1)
+ integer, allocatable :: xx1(..)
+ type(t), allocatable :: yy1(..)
+ if (.not. allocated (xx1)) call abort ()
+ if (.not. allocated (yy1)) call abort ()
+ end subroutine faa
+ subroutine fai (xx1, yy1)
+ integer, allocatable, intent(in) :: xx1(..)
+ type(t), allocatable, intent(in) :: yy1(..)
+ if (.not. allocated (xx1)) call abort ()
+ if (.not. allocated (yy1)) call abort ()
+ end subroutine fai
+ subroutine fpa (xx1, yy1)
+ integer, pointer :: xx1(..)
+ type(t), pointer :: yy1(..)
+ if (is_present .neqv. associated (xx1)) call abort ()
+ if (is_present .neqv. associated (yy1)) call abort ()
+ end subroutine fpa
+
+ subroutine fpi (xx1, yy1)
+ integer, pointer, intent(in) :: xx1(..)
+ type(t), pointer, intent(in) :: yy1(..)
+ if (is_present .neqv. associated (xx1)) call abort ()
+ if (is_present .neqv. associated (yy1)) call abort ()
+ end subroutine fpi
+
+ subroutine fnn(xx2,yy2)
+ integer :: xx2(..)
+ type(t) :: yy2(..)
+ end subroutine fnn
+
+ subroutine fno(xx2,yy2)
+ integer, optional :: xx2(..)
+ type(t), optional :: yy2(..)
+ if (is_present .neqv. present (xx2)) call abort ()
+ if (is_present .neqv. present (yy2)) call abort ()
+ end subroutine fno
+end program test
+
+! We should have exactly one copy back per variable
+!
+! { dg-final { scan-tree-dump-times "iip = .integer.kind=4. .. desc.\[0-9\]+.data;" 1 "original" } }
+! { dg-final { scan-tree-dump-times "iia = .integer.kind=4. .. desc.\[0-9\]+.data;" 1 "original" } }
+! { dg-final { scan-tree-dump-times "jjp = .struct t .. desc.\[0-9\]+.data;" 1 "original" } }
+! { dg-final { scan-tree-dump-times "jja = .struct t .. desc.\[0-9\]+.data;" 1 "original" } }
+! { dg-final { cleanup-tree-dump "original" } }