aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/auto_char_dummy_array_3.f90
blob: 053956cabfd283849f7a7f422a551d7ab0eaa6e8 (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
! { dg-do run }

! PR fortran/49885
! Check that character arrays with non-constant char-length are handled
! correctly.

! Contributed by Daniel Kraft <d@domob.eu>,
! based on original test case and variant by Tobias Burnus in comment 2.

PROGRAM main
  IMPLICIT NONE

  CALL s (10)
      
CONTAINS

  SUBROUTINE s (nb)
    INTEGER :: nb
    CHARACTER(MAX (80, nb)) :: bad_rec(1)

    bad_rec(1)(1:2) = 'abc'
    IF (bad_rec(1)(1:2) /= 'ab') CALL abort ()
  END SUBROUTINE s

END PROGRAM main