aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/array_constructor_type_7.f03
blob: 8fb210a68c63a54f3ea192b4c16d4f43c1da4552 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
! { dg-do run }
! { dg-options "-fbounds-check" }
!
! PR fortran/27997
!
! Array constructor with typespec and dynamic
! character length.
!
PROGRAM test
  CALL foo(8, "short", "test", "short")
  CALL foo(2, "lenghty", "te", "le")
CONTAINS
  SUBROUTINE foo (n, s, a1, a2)
    CHARACTER(len=*) :: s
    CHARACTER(len=*) :: a1, a2
    CHARACTER(len=n) :: arr(2)
    INTEGER :: n
    arr = [ character(len=n) :: 'test', s ]
    IF (arr(1) /= a1 .OR. arr(2) /= a2) THEN
      CALL abort ()
    END IF
  END SUBROUTINE foo
END PROGRAM test