./:
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr17612.f90
blob1b6853269ab297c7d8c8cd52bf9acde74a54f950
1 ! { dg-do run }
2 ! PR 17612
3 ! We used to not determine the length of character-valued expressions
4 ! correctly, leading to a segfault.
5 program prog
6 character(len=2), target :: c(4)
7 type pseudo_upf
8 character(len=2), pointer :: els(:)
9 end type pseudo_upf
10 type (pseudo_upf) :: p
11 type t
12 character(5) :: s(2)
13 end type
14 type (t) v
15 ! A full arrays.
16 c = (/"ab","cd","ef","gh"/)
17 call n(p)
18 if (any (c /= p%els)) call abort
19 ! An array section that needs a new array descriptor.
20 v%s(1) = "hello"
21 v%s(2) = "world"
22 call test (v%s)
23 contains
25 subroutine n (upf)
26 type (pseudo_upf), intent(inout) :: upf
27 upf%els => c
28 return
29 end subroutine n
31 subroutine test(s)
32 character(len=*) :: s(:)
33 if ((len (s) .ne. 5) .or. (any (s .ne. (/"hello", "world"/)))) call abort
34 end subroutine
35 end program