Merge reload-branch up to revision 101000
[official-gcc.git] / gcc / testsuite / gfortran.dg / char_pointer_dependency.f90
blob94976cbb33c63b6c17145ce2a0e763f12588b191
1 ! { dg-do run }
2 ! Test assignments from character pointer functions with dependencies
3 ! are correctly resolved.
4 ! Provided by Paul Thomas pault@gcc.gnu.org
5 program char_pointer_dependency
6 implicit none
7 character*4, pointer :: c2(:)
8 allocate (c2(2))
9 c2 = (/"abcd","efgh"/)
10 c2 = afoo (c2)
11 if (c2(1) /= "efgh") call abort ()
12 if (c2(2) /= "abcd") call abort ()
13 deallocate (c2)
14 contains
15 function afoo (ac0) result (ac1)
16 integer :: j
17 character*4 :: ac0(:)
18 character*4, pointer :: ac1(:)
19 allocate (ac1(2))
20 do j = 1,2
21 ac1(j) = ac0(3-j)
22 end do
23 end function afoo
24 end program char_pointer_dependency