summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/finalize_16.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/finalize_16.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/finalize_16.f9032
1 files changed, 32 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/finalize_16.f90 b/gcc/testsuite/gfortran.dg/finalize_16.f90
new file mode 100644
index 0000000000..89c5cfb8d9
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/finalize_16.f90
@@ -0,0 +1,32 @@
+! { dg-do compile }
+! { dg-options "-fcheck=all" }
+!
+! PR fortran/57542
+!
+! Contributed by Salvatore Filippone
+!
+module type_mod
+ type inner
+ end type inner
+
+ type outer
+ class(inner), allocatable :: item
+ end type outer
+
+ type container
+ class(outer), allocatable :: item
+ end type container
+
+ type maintype
+ type(container), allocatable :: v(:)
+ end type maintype
+
+end module type_mod
+
+subroutine testfinal(var)
+ use type_mod
+ type(maintype), intent(inout) :: var
+ ! A real code would obviously check
+ ! this is really allocated
+ deallocate(var%v(1)%item%item)
+end subroutine testfinal