aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/alloc_comp_assign_4.f90
blob: b204106da2d1de9b9373a718097c7b44396a62de (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
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
! { dg-do run }
! Test assignments of nested derived types with character allocatable
! components(PR 20541). Subroutine test_ab6 checks out a bug in a test
! version of gfortran's allocatable arrays.
!
! Contributed by Erik Edelmann  <eedelmann@gcc.gnu.org>
!            and Paul Thomas  <pault@gcc.gnu.org>
!
  type :: a
    character(4), allocatable :: ch(:)
  end type a

  type :: b
    type (a), allocatable :: at(:)
  end type b

  type(a) :: x(2)
  type(b) :: y(2), z(2)

  character(4) :: chr1(4) = (/"abcd","efgh","ijkl","mnop"/)
  character(4) :: chr2(4) = (/"qrst","uvwx","yz12","3456"/)

  x(1) = a(chr1)

 ! Check constructor with character array constructors.
  x(2) = a((/"qrst","uvwx","yz12","3456"/))

  y(1) = b((/x(1),x(2)/))
  y(2) = b((/x(2),x(1)/))

  y(2) = y(1)

  if (any((/((y(2)%at(i)%ch(j),j=1,4),i=1,2)/) .ne. &
          (/chr1, chr2/))) call abort ()

  call test_ab6 ()

contains

  subroutine test_ab6 ()
! This subroutine tests the presence of a scalar derived type, intermediate
! in a chain of derived types with allocatable components.
! Contributed by Salvatore Filippone  <salvatore.filippone@uniroma2.it>

    type b
      type(a)  :: a
    end type b

    type c
      type(b), allocatable :: b(:) 
    end type c

    type(c)    :: p
    type(b)   :: bv

    p = c((/b(a((/"Mary","Lamb"/)))/))
    bv = p%b(1)

    if (any ((bv%a%ch(:)) .ne. (/"Mary","Lamb"/))) call abort ()

end subroutine test_ab6

end