URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [class_allocate_6.f03] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do run }!! PR 46174: [OOP] ALLOCATE with SOURCE: Deep copy missing!! Contributed by Tobias Burnus <burnus@gcc.gnu.org>implicit nonetype tend type ttype, extends(t) :: t2integer, allocatable :: a(:)end type t2class(t), allocatable :: x, yinteger :: iallocate(t2 :: x)select type(x)type is (t2)allocate(x%a(10))x%a = [ (i, i = 1,10) ]print '(*(i3))', x%aclass defaultcall abort()end selectallocate(y, source=x)select type(x)type is (t2)x%a = [ (i, i = 11,20) ]print '(*(i3))', x%aclass defaultcall abort()end selectselect type(y)type is (t2)print '(*(i3))', y%aif (any (y%a /= [ (i, i = 1,10) ])) call abort()class defaultcall abort()end selectend
