OSDN Git Service

2012-01-30 Richard Guenther <rguenther@suse.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / alloc_comp_assign_11.f90
1 ! { dg-do run }
2 !
3 ! PR fortran/49324
4 !
5 ! Check that with array constructors a deep copy is done
6 !
7 implicit none
8 type t
9   integer, allocatable :: A(:)
10 end type t
11
12 type(t) :: x, y
13 type(t), allocatable :: z(:), z2(:)
14
15 allocate (x%A(2))
16 allocate (y%A(1))
17 x%A(:) = 11
18 y%A(:) = 22
19
20 allocate (z(2))
21
22 z = [ x, y ]
23 !print *, z(1)%a, z(2)%a, x%A, y%A
24 if (any (z(1)%a /= 11) .or. z(2)%a(1) /= 22 .or. any (x%A /= 11)  &
25     .or. y%A(1) /= 22)  &
26   call abort()
27
28 x%A(:) = 444
29 y%A(:) = 555
30
31 !print *, z(1)%a, z(2)%a, x%A, y%A
32 if (any (z(1)%a /= 11) .or. z(2)%a(1) /= 22 .or. any (x%A /= 444)  &
33     .or. y%A(1) /= 555)  &
34   call abort()
35
36 z(:) = [ x, y ]
37 !print *, z(1)%a, z(2)%a, x%A, y%A
38 if (any (z(1)%a /= 444) .or. z(2)%a(1) /= 555 .or. any (x%A /= 444)  &
39     .or. y%A(1) /= 555)  &
40   call abort()
41 end