OSDN Git Service

* trans.c (trans_code): Set backend locus early.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / class_allocate_4.f03
1 ! { dg-do run }
2 !
3 ! PR 41714: [OOP] ALLOCATE SOURCE= does not properly copy the value from SOURCE
4 !
5 ! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
6
7 type t
8   integer :: i
9 end type t
10 type, extends(t) :: t2
11   integer :: j
12 end type t2
13
14 class(t), allocatable :: a
15 allocate(a, source=t2(1,2))
16 print *,a%i
17 if(a%i /= 1) call abort()
18 select type (a)
19   type is (t2)
20      print *,a%j
21      if(a%j /= 2) call abort()
22 end select
23 end