URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [char_array_structure_constructor.f90] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do run }! { dg-options "-fwhole-file" }!! PR fortran/19107! -fwhole-file flag added for PR fortran/44945!! This test the fix of PR19107, where character array actual! arguments in derived type constructors caused an ICE.! It also checks that the scalar counterparts are OK.! Contributed by Paul Thomas pault@gcc.gnu.org!MODULE globalTYPE :: dtCHARACTER(4) aCHARACTER(4) b(2)END TYPETYPE (dt), DIMENSION(:), ALLOCATABLE, SAVE :: cEND MODULE globalprogram char_array_structure_constructorUSE globalcall alloc (2)if ((any (c%a /= "wxyz")) .OR. &(any (c%b(1) /= "abcd")) .OR. &(any (c%b(2) /= "efgh"))) call abort ()containsSUBROUTINE alloc (n)USE globalALLOCATE (c(n), STAT=IALLOC_FLAG)DO i = 1,nc (i) = dt ("wxyz",(/"abcd","efgh"/))ENDDOend subroutine allocEND program char_array_structure_constructor! { dg-final { cleanup-modules "global" } }
