view gcc/testsuite/gfortran.dg/char_pointer_dummy.f90 @ 145:1830386684a0

gcc-9.2.0
author anatofuz
date Thu, 13 Feb 2020 11:34:05 +0900
parents 84e7813d76e9
children
line wrap: on
line source

! { dg-do run }
! { dg-options "-std=legacy" }
!
program char_pointer_dummy
! Test character pointer dummy arguments, required
! to fix PR16939 and PR18689
! Provided by Paul Thomas pault@gcc.gnu.org
  implicit none
  character*4                :: c0
  character*4, pointer       :: c1
  character*4, pointer       :: c2(:)
  allocate (c1, c2(1))
! Check that we have not broken non-pointer characters.
  c0 = "wxyz"
  call foo (c0)
! Now the pointers
  c1 = "wxyz"
  call sfoo (c1)
  c2 = "wxyz"
  call afoo (c2)
  deallocate (c1, c2)
contains
  subroutine foo (cc1)
    character*4                :: cc1
    if (cc1 /= "wxyz") STOP 1
  end subroutine foo
  subroutine sfoo (sc1)
    character*4, pointer       :: sc1
    if (sc1 /= "wxyz") STOP 2
  end subroutine sfoo
  subroutine afoo (ac1)
    character*4, pointer       :: ac1(:)
    if (ac1(1) /= "wxyz") STOP 3
  end subroutine afoo
end program char_pointer_dummy