summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/allocate_with_source_9.f08
blob: 5be70c996558b6313358abc16cf6e2fdd5627e0a (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
! { dg-do run }
!
! Contributed by Thomas Koenig  <tkoenig@gcc.gnu.org>,
!                Andre Vehreschild  <vehre@gcc.gnu.org>

program main

  type T
     integer, allocatable :: acc(:)
  end type

  integer :: n, lb, ub
  integer :: vec(9)
  type(T) :: o1, o2
  vec = [(i, i= 1, 9)]
  n = 42
  lb = 7
  ub = lb + 2
  allocate(o1%acc, source=vec)
  allocate(o2%acc, source=o1%acc(lb:ub))
  if (any (o2%acc /= [7, 8, 9])) STOP 1
  block
    real, dimension(0:n) :: a
    real, dimension(:), allocatable :: c
    call random_number(a)
    allocate(c,source=a(:))
    if (any (abs(a - c) > 1E-6)) STOP 2
  end block
end program main