aarch64: Add missing ACLE macro for NEON-SVE Bridge
[official-gcc.git] / gcc / testsuite / gfortran.dg / class_allocate_5.f90
blob3af3e84953f279c85c247b1e56412d6921d7775f
1 ! { dg-do run }
3 ! PR fortran/45451
5 ! Contributed by Salvatore Filippone and Janus Weil
7 ! Check that ALLOCATE with SOURCE= does a deep copy.
9 program bug23
10 implicit none
12 type :: psb_base_sparse_mat
13 integer, allocatable :: irp(:)
14 end type psb_base_sparse_mat
16 class(psb_base_sparse_mat), allocatable :: a
17 type(psb_base_sparse_mat) :: acsr
19 allocate(acsr%irp(4))
20 acsr%irp(1:4) = (/1,3,4,5/)
22 write(*,*) acsr%irp(:)
24 allocate(a,source=acsr)
26 write(*,*) a%irp(:)
28 call move_alloc(acsr%irp, a%irp)
30 write(*,*) a%irp(:)
32 if (any (a%irp /= [1,3,4,5])) STOP 1
33 end program bug23