view gcc/testsuite/gfortran.dg/pr15129.f90 @ 118:fd00160c1b76

ifdef TARGET_64BIT
author mir3636
date Tue, 27 Feb 2018 15:01:35 +0900
parents 04ced10e8804
children 84e7813d76e9
line wrap: on
line source

! { dg-do run }
! { dg-options "-std=legacy" }
!
! PR 15129: we used to share the character length between A and B in the 
! subroutine.
CHARACTER*10 A
CHARACTER*8 B
A = 'gfortran'
B = 'rocks!'
CALL T(A,B)
contains
SUBROUTINE T(A,B)
CHARACTER*(*) A,B
if(len(a)/=10) call abort()
if(len(b)/=8) call abort()
END SUBROUTINE
end