summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/class_allocate_5.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/class_allocate_5.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/class_allocate_5.f9034
1 files changed, 34 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/class_allocate_5.f90 b/gcc/testsuite/gfortran.dg/class_allocate_5.f90
new file mode 100644
index 000000000..592161ef5
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/class_allocate_5.f90
@@ -0,0 +1,34 @@
+! { dg-do run }
+!
+! PR fortran/45451
+!
+! Contributed by Salvatore Filippone and Janus Weil
+!
+! Check that ALLOCATE with SOURCE= does a deep copy.
+!
+program bug23
+ implicit none
+
+ type :: psb_base_sparse_mat
+ integer, allocatable :: irp(:)
+ end type psb_base_sparse_mat
+
+ class(psb_base_sparse_mat), allocatable :: a
+ type(psb_base_sparse_mat) :: acsr
+
+ allocate(acsr%irp(4))
+ acsr%irp(1:4) = (/1,3,4,5/)
+
+ write(*,*) acsr%irp(:)
+
+ allocate(a,source=acsr)
+
+ write(*,*) a%irp(:)
+
+ call move_alloc(acsr%irp, a%irp)
+
+ write(*,*) a%irp(:)
+
+ if (any (a%irp /= [1,3,4,5])) call abort()
+end program bug23
+