OpenCores
URL https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk

Subversion Repositories openrisc_2011-10-31

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [char_array_structure_constructor.f90] - Blame information for rev 154

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 149 jeremybenn
! { dg-do run }
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
6
!
7
MODULE global
8
  TYPE :: dt
9
    CHARACTER(4) a
10
    CHARACTER(4) b(2)
11
  END TYPE
12
  TYPE (dt), DIMENSION(:), ALLOCATABLE, SAVE :: c
13
END MODULE global
14
program char_array_structure_constructor
15
  USE global
16
  call alloc (2)
17
  if ((any (c%a /= "wxyz")) .OR. &
18
      (any (c%b(1) /= "abcd")) .OR. &
19
      (any (c%b(2) /= "efgh"))) call abort ()
20
contains
21
  SUBROUTINE alloc (n)
22
    USE global
23
    ALLOCATE (c(n), STAT=IALLOC_FLAG)
24
    DO i = 1,n
25
      c (i) = dt ("wxyz",(/"abcd","efgh"/))
26
    ENDDO
27
  end subroutine alloc
28
END program char_array_structure_constructor
29
 
30
! { dg-final { cleanup-modules "global" } }

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.