Dead
[official-gcc.git] / gomp-20050608-branch / gcc / testsuite / gfortran.dg / auto_char_dummy_array_1.f90
blob2ee98cfcc806498cfd666b1eb30ecb447620d06f
1 ! { dg-do run }
2 ! This tests the fix for pr15809 in which automatic character length,
3 ! dummy, pointer arrays were broken.
5 ! contributed by Paul Thomas <pault@gcc.gnu.org>
7 module global
8 character(12), dimension(2), target :: t
9 end module global
11 program oh_no_not_pr15908_again
12 character(12), dimension(:), pointer :: ptr
14 call a (ptr, 12)
15 if (.not.associated (ptr) ) call abort ()
16 if (any (ptr.ne."abc")) call abort ()
18 ptr => null () ! ptr points to 't' here.
19 allocate (ptr(3))
20 ptr = "xyz"
21 call a (ptr, 12)
23 if (.not.associated (ptr)) call abort ()
24 if (any (ptr.ne."lmn")) call abort ()
26 call a (ptr, 0)
28 if (associated (ptr)) call abort ()
30 contains
32 subroutine a (p, l)
33 use global
34 character(l), dimension(:), pointer :: p
35 character(l), dimension(3) :: s
37 s = "lmn"
39 if (l.ne.12) then
40 deallocate (p) ! ptr was allocated in main.
41 p => null ()
42 return
43 end if
45 if (.not.associated (p)) then
46 t = "abc"
47 p => t
48 else
49 if (size (p,1).ne.3) call abort ()
50 if (any (p.ne."xyz")) call abort ()
51 p = s
52 end if
53 end subroutine a
55 end program oh_no_not_pr15908_again