aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/class_allocate_23.f08
blob: 5c83fbe96180f5df87f661fbef1b9426dba8daed (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
! { dg-do run }
!
! Test that pr78356 is fixed.
! Contributed by Janus Weil and Andrew Benson

program p
  implicit none
  type ac
  end type
  type, extends(ac) :: a
     integer, allocatable :: b
  end type
  type n
     class(ac), allocatable :: acr(:)
  end type
  type(n) :: s,t
  allocate(a :: s%acr(1))
  call nncp(s,t)
  select type (cl => t%acr(1))
    class is (a)
      if (allocated(cl%b)) error stop
    class default
      error stop
  end select
contains
  subroutine nncp(self,tg)
    type(n) :: self, tg
    allocate(tg%acr(1),source=self%acr(1))
  end
end