OSDN Git Service

* trans.c (trans_code): Set backend locus early.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / array_constructor_13.f90
1 ! { dg-do compile }
2 ! { dg-options "-std=legacy" }
3 !
4 ! Tests patch for PR29431, which arose from PR29373.
5 !
6 ! Contributed by Tobias Schlueter  <tobi@gcc.gnu.org>
7 !
8   implicit none
9   CHARACTER(len=6), DIMENSION(2,2)  :: a
10
11 ! Reporters original triggered another error:
12 ! gfc_todo: Not Implemented: complex character array
13 ! constructors.
14
15   a = reshape([to_string(1.0), trim("abcdef"), &
16                to_string(7.0), trim("hijklm")], &
17                [2, 2])
18   print *, a
19
20   CONTAINS
21     FUNCTION to_string(x)
22       character*6 to_string
23       REAL, INTENT(in) :: x
24       WRITE(to_string, FMT="(F6.3)") x
25     END FUNCTION
26 end