PR rtl-optimization/82913
[official-gcc.git] / gcc / testsuite / gfortran.dg / auto_char_pointer_array_result_1.f90
blob8e3eb94c261c00389f81409a8fed79d5d828015b
1 ! { dg-do run }
2 ! Tests the fixes for PR25597 and PR27096.
4 ! This test combines the PR testcases.
6 character(10), dimension (2) :: implicit_result
7 character(10), dimension (2) :: explicit_result
8 character(10), dimension (2) :: source
9 source = "abcdefghij"
10 explicit_result = join_1(source)
11 if (any (explicit_result .ne. source)) call abort ()
13 implicit_result = reallocate_hnv (source, size(source, 1), LEN (source))
14 if (any (implicit_result .ne. source)) call abort ()
16 contains
18 ! This function would cause an ICE in gfc_trans_deferred_array.
19 function join_1(self) result(res)
20 character(len=*), dimension(:) :: self
21 character(len=len(self)), dimension(:), pointer :: res
22 allocate (res(2))
23 res = self
24 end function
26 ! This function originally ICEd and latterly caused a runtime error.
27 FUNCTION reallocate_hnv(p, n, LEN)
28 CHARACTER(LEN=LEN), DIMENSION(:), POINTER :: reallocate_hnv
29 character(*), dimension(:) :: p
30 ALLOCATE (reallocate_hnv(n))
31 reallocate_hnv = p
32 END FUNCTION reallocate_hnv
34 end