c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / auto_char_dummy_array_1.f90
blobd94f81af3c62a7ca9cce11932c35d7fa6b6cb532
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 nullify(ptr)
16 call a (ptr, 12)
17 if (.not.associated (ptr) ) STOP 1
18 if (any (ptr.ne."abc")) STOP 2
20 ptr => null () ! ptr points to 't' here.
21 allocate (ptr(3))
22 ptr = "xyz"
23 call a (ptr, 12)
25 if (.not.associated (ptr)) STOP 3
26 if (any (ptr.ne."lmn")) STOP 4
28 call a (ptr, 0)
30 if (associated (ptr)) STOP 5
32 contains
34 subroutine a (p, l)
35 use global
36 character(l), dimension(:), pointer :: p
37 character(l), dimension(3) :: s
39 s = "lmn"
41 if (l.ne.12) then
42 deallocate (p) ! ptr was allocated in main.
43 p => null ()
44 return
45 end if
47 if (.not.associated (p)) then
48 t = "abc"
49 p => t
50 else
51 if (size (p,1).ne.3) STOP 6
52 if (any (p.ne."xyz")) STOP 7
53 p = s
54 end if
55 end subroutine a
57 end program oh_no_not_pr15908_again