* tree-loop-distribution.c (struct partition): New field recording
[official-gcc.git] / gcc / testsuite / gfortran.dg / class_allocate_22.f90
blob5fec72fafe130c64f68288dacbf945f359dab7d0
1 ! { dg-do run }
3 ! Check pr57117 is fixed.
5 program pr57117
6 implicit none
8 type :: ti
9 integer :: i
10 end type
12 class(ti), allocatable :: x(:,:), y(:,:)
13 integer :: i
15 allocate(x(2,6))
16 select type (x)
17 class is (ti)
18 x%i = reshape([(i,i=1, 12)],[2,6])
19 end select
20 allocate(y, source=transpose(x))
22 if (any( ubound(y) /= [6,2])) call abort()
23 if (any(reshape(y(:,:)%i, [12]) /= [ 1,3,5,7,9,11, 2,4,6,8,10,12])) call abort()
24 deallocate (x,y)
25 end