* tree-loop-distribution.c (struct partition): New field recording
[official-gcc.git] / gcc / testsuite / gfortran.dg / nested_array_constructor_3.f90
blobdd10e5fafc9cb185999c6ebd734ee4e82cb9b8da
1 ! { dg-do run }
3 ! PR fortran/35846
4 ! Alternate test that also produced an ICE because of a missing length.
6 PROGRAM test
7 IMPLICIT NONE
8 CHARACTER(LEN=2) :: x
10 x = 'a'
11 CALL sub ( (/ TRIM(x), 'a' /) // 'c')
12 END PROGRAM
14 SUBROUTINE sub(str)
15 IMPLICIT NONE
16 CHARACTER(LEN=*) :: str(2)
17 WRITE (*,*) str
19 IF (str(1) /= 'ac' .OR. str(2) /= 'ac') THEN
20 CALL abort ()
21 END IF
22 END SUBROUTINE sub