summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/unlimited_polymorphic_3.f03
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/unlimited_polymorphic_3.f03')
-rw-r--r--gcc/testsuite/gfortran.dg/unlimited_polymorphic_3.f0356
1 files changed, 39 insertions, 17 deletions
diff --git a/gcc/testsuite/gfortran.dg/unlimited_polymorphic_3.f03 b/gcc/testsuite/gfortran.dg/unlimited_polymorphic_3.f03
index 075d6d727e2..00dd2ae1199 100644
--- a/gcc/testsuite/gfortran.dg/unlimited_polymorphic_3.f03
+++ b/gcc/testsuite/gfortran.dg/unlimited_polymorphic_3.f03
@@ -1,4 +1,5 @@
! { dg-do run }
+! { dg-additional-options "-fdump-tree-dse-details" }
!
! Check that pointer assignments allowed by F2003:C717
! work and check null initialization of CLASS(*) pointers.
@@ -7,20 +8,31 @@
!
program main
interface
- subroutine foo(z)
+ subroutine foo_bc(z)
class(*), pointer, intent(in) :: z
- end subroutine foo
+ end subroutine foo_bc
+ subroutine foo_sq(z)
+ class(*), pointer, intent(in) :: z
+ end subroutine foo_sq
end interface
+ type, bind(c) :: bc
+ integer :: i
+ end type bc
type sq
sequence
- integer :: i
+ integer :: k
end type sq
+ type(bc), target :: w
type(sq), target :: x
class(*), pointer :: y, z
- x%i = 42
+ w%i = 23
+ y => w
+ z => y ! unlimited => unlimited allowed
+ call foo_bc(z)
+ x%k = 42
y => x
z => y ! unlimited => unlimited allowed
- call foo (z)
+ call foo_sq(z)
call bar
contains
subroutine bar
@@ -33,21 +45,31 @@ contains
end program main
-
-subroutine foo(tgt)
+subroutine foo_bc(tgt)
use iso_c_binding
class(*), pointer, intent(in) :: tgt
- type, bind(c) :: s
- integer (c_int) :: k
- end type s
- type t
+ type, bind(c) :: bc
+ integer (c_int) :: i
+ end type bc
+ type(bc), pointer :: ptr1
+ ptr1 => tgt ! bind(c) => unlimited allowed
+ if (ptr1%i .ne. 23) STOP 2
+end subroutine foo_bc
+
+subroutine foo_sq(tgt)
+ class(*), pointer, intent(in) :: tgt
+ type sq
sequence
integer :: k
- end type t
- type(s), pointer :: ptr1
- type(t), pointer :: ptr2
- ptr1 => tgt ! bind(c) => unlimited allowed
- if (ptr1%k .ne. 42) STOP 2
+ end type sq
+ type(sq), pointer :: ptr2
ptr2 => tgt ! sequence type => unlimited allowed
if (ptr2%k .ne. 42) STOP 3
-end subroutine foo
+end subroutine foo_sq
+
+! PR fortran/103662
+! We used to produce multiple independant types for the unlimited polymorphic
+! descriptors (types for class(*)) which caused stores to them to be seen as
+! useless.
+! { dg-final { scan-tree-dump-not "Deleted dead store: z._data = &w" "dse1" { target __OPTIMIZE__ } } }
+! { dg-final { scan-tree-dump-not "Deleted dead store: z._data = &x" "dse1" { target __OPTIMIZE__ } } }