aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/auto_char_dummy_array_1.f90
blob: d94f81af3c62a7ca9cce11932c35d7fa6b6cb532 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
! { dg-do run }
! This tests the fix for pr15809 in which automatic character length,
! dummy, pointer arrays were broken.
!
! contributed by Paul Thomas  <pault@gcc.gnu.org>
!
module global
  character(12), dimension(2), target :: t
end module global

program oh_no_not_pr15908_again
  character(12), dimension(:), pointer :: ptr

  nullify(ptr)

  call a (ptr, 12)
  if (.not.associated (ptr) ) STOP 1
  if (any (ptr.ne."abc")) STOP 2

  ptr => null ()              ! ptr points to 't' here.
  allocate (ptr(3))
  ptr = "xyz"
  call a (ptr, 12)

  if (.not.associated (ptr)) STOP 3
  if (any (ptr.ne."lmn")) STOP 4

  call a (ptr, 0)

  if (associated (ptr)) STOP 5

contains

  subroutine a (p, l)
    use global
    character(l), dimension(:), pointer :: p
    character(l), dimension(3)          :: s

    s = "lmn"

    if (l.ne.12) then
      deallocate (p)           ! ptr was allocated in main.
      p => null ()
      return
    end if

    if (.not.associated (p)) then
      t = "abc"
      p => t
    else
      if (size (p,1).ne.3) STOP 6
      if (any (p.ne."xyz")) STOP 7
      p = s
    end if
  end subroutine a

end program oh_no_not_pr15908_again