OSDN Git Service

* config/i386/i386.md (UNSPEC_VSIBADDR): New.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / class_allocate_5.f90
1 ! { dg-do run }
2 !
3 ! PR fortran/45451
4 !
5 ! Contributed by Salvatore Filippone and Janus Weil
6 !
7 ! Check that ALLOCATE with SOURCE= does a deep copy.
8 !
9 program bug23
10   implicit none
11
12   type  :: psb_base_sparse_mat
13     integer, allocatable :: irp(:)
14   end type psb_base_sparse_mat
15
16   class(psb_base_sparse_mat), allocatable  :: a 
17   type(psb_base_sparse_mat) :: acsr
18
19   allocate(acsr%irp(4)) 
20   acsr%irp(1:4) = (/1,3,4,5/)
21
22   write(*,*) acsr%irp(:)
23
24   allocate(a,source=acsr)
25
26   write(*,*) a%irp(:)
27
28   call move_alloc(acsr%irp, a%irp)
29
30   write(*,*) a%irp(:)
31
32   if (any (a%irp /= [1,3,4,5])) call abort()
33 end program bug23
34