arm: Add .type and .size to __gnu_cmse_nonsecure_call [PR115360]
[official-gcc.git] / gcc / testsuite / gfortran.dg / allocate_with_source_9.f08
blob5be70c996558b6313358abc16cf6e2fdd5627e0a
1 ! { dg-do run }
3 ! Contributed by Thomas Koenig  <tkoenig@gcc.gnu.org>,
4 !                Andre Vehreschild  <vehre@gcc.gnu.org>
6 program main
8   type T
9      integer, allocatable :: acc(:)
10   end type
12   integer :: n, lb, ub
13   integer :: vec(9)
14   type(T) :: o1, o2
15   vec = [(i, i= 1, 9)]
16   n = 42
17   lb = 7
18   ub = lb + 2
19   allocate(o1%acc, source=vec)
20   allocate(o2%acc, source=o1%acc(lb:ub))
21   if (any (o2%acc /= [7, 8, 9])) STOP 1
22   block
23     real, dimension(0:n) :: a
24     real, dimension(:), allocatable :: c
25     call random_number(a)
26     allocate(c,source=a(:))
27     if (any (abs(a - c) > 1E-6)) STOP 2
28   end block
29 end program main