OSDN Git Service

2011-09-26 Janus Weil <janus@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / char_array_structure_constructor.f90
1 ! { dg-do run }
2 ! { dg-options "-fwhole-file" }
3 !
4 ! PR fortran/19107
5 ! -fwhole-file flag added for PR fortran/44945
6 !
7 ! This test the fix of PR19107, where character array actual
8 ! arguments in derived type constructors caused an ICE.
9 ! It also checks that the scalar counterparts are OK.
10 ! Contributed by Paul Thomas  pault@gcc.gnu.org
11 !
12 MODULE global
13   TYPE :: dt
14     CHARACTER(4) a
15     CHARACTER(4) b(2)
16   END TYPE
17   TYPE (dt), DIMENSION(:), ALLOCATABLE, SAVE :: c
18 END MODULE global
19 program char_array_structure_constructor
20   USE global
21   call alloc (2)
22   if ((any (c%a /= "wxyz")) .OR. &
23       (any (c%b(1) /= "abcd")) .OR. &
24       (any (c%b(2) /= "efgh"))) call abort ()
25 contains
26   SUBROUTINE alloc (n)
27     USE global
28     ALLOCATE (c(n), STAT=IALLOC_FLAG)
29     DO i = 1,n
30       c (i) = dt ("wxyz",(/"abcd","efgh"/))
31     ENDDO
32   end subroutine alloc
33 END program char_array_structure_constructor
34
35 ! { dg-final { cleanup-modules "global" } }