OpenCores
URL https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk

Subversion Repositories openrisc_2011-10-31

[/] [openrisc/] [tags/] [gnu-src/] [gcc-4.5.1/] [gcc-4.5.1-or32-1.0rc2/] [gcc/] [testsuite/] [gfortran.dg/] [nested_array_constructor_3.f90] - Blame information for rev 384

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 302 jeremybenn
! { dg-do run }
2
 
3
! PR fortran/35846
4
! Alternate test that also produced an ICE because of a missing length.
5
 
6
PROGRAM test
7
  IMPLICIT NONE
8
  CHARACTER(LEN=2) :: x
9
 
10
  x = 'a'
11
  CALL sub ( (/ TRIM(x), 'a' /) // 'c')
12
END PROGRAM
13
 
14
SUBROUTINE sub(str)
15
  IMPLICIT NONE
16
  CHARACTER(LEN=*) :: str(2)
17
  WRITE (*,*) str
18
 
19
  IF (str(1) /= 'ac' .OR. str(2) /= 'ac') THEN
20
    CALL abort ()
21
  END IF
22
END SUBROUTINE sub

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.