lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr67740.f90
blobbf70ff223632d05faaecb85bf716cb0272986941
1 ! { dg-do compile }
2 ! { dg-options "-fdump-tree-original" }
4 ! Check the fix for the testcase in comment 4, where the hidden string length
5 ! component of the array pointer component was not set.
7 ! Contributed by Sebastien Bardeau <bardeau@iram.fr>
9 program test2
10 implicit none
11 character(len=10), allocatable, target :: s(:)
12 character(len=:), pointer :: sptr(:)
13 type :: pointer_typec0_t
14 character(len=:), pointer :: data0
15 character(len=:), pointer :: data1(:)
16 end type pointer_typec0_t
17 type(pointer_typec0_t) :: co
19 allocate(s(3))
20 s(1) = '1234567890'
21 s(2) = 'qwertyuio '
22 s(3) = 'asdfghjk '
24 sptr => s
25 co%data0 => s(1)
26 co%data1 => s
28 if (any (sptr .ne. s)) stop 1
29 if (co%data0 .ne. s(1)) stop 2
30 if (any (co%data1 .ne. s)) stop 3 ! Hidden string length was not set
31 end program test2
32 ! { dg-final { scan-tree-dump-times "co._data1_length = 10;" 1 "original" } }