2 ! This test the fix of PR19107, where character array actual
3 ! arguments in derived type constructors caused an ICE.
4 ! It also checks that the scalar counterparts are OK.
5 ! Contributed by Paul Thomas pault@gcc.gnu.org
12 TYPE (dt
), DIMENSION(:), ALLOCATABLE
, SAVE :: c
14 program char_array_structure_constructor
17 if ((any (c
%a
/= "wxyz")) .OR
. &
18 (any (c
%b(1) /= "abcd")) .OR
. &
19 (any (c
%b(2) /= "efgh"))) call abort ()
23 ALLOCATE (c(n
), STAT
=IALLOC_FLAG
)
25 c (i
) = dt ("wxyz",(/"abcd","efgh"/))
28 END program char_array_structure_constructor
30 ! { dg-final { cleanup-modules "global" } }