view gcc/testsuite/gfortran.dg/class_allocate_22.f90 @ 152:2b5abeee2509

update gcc11
author anatofuz
date Mon, 25 May 2020 07:50:57 +0900
parents 84e7813d76e9
children
line wrap: on
line source

! { dg-do run }
!
! Check pr57117 is fixed.

program pr57117
  implicit none

  type :: ti
    integer :: i
  end type

  class(ti), allocatable :: x(:,:), y(:,:)
  integer :: i

  allocate(x(2,6))
  select type (x)
    class is (ti)
       x%i = reshape([(i,i=1, 12)],[2,6])
  end select
  allocate(y, source=transpose(x))

  if (any( ubound(y) /= [6,2])) STOP 1
  if (any(reshape(y(:,:)%i, [12]) /= [ 1,3,5,7,9,11, 2,4,6,8,10,12])) STOP 2
  deallocate (x,y)
end