OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [automatic_default_init_1.f90] - Blame information for rev 715

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do run }
2
! { dg-options "-O" }
3
! Test the fix for PR29394 in which automatic arrays did not
4
! get default initialization.
5
! Contributed by Francois-Xavier Coudert  
6
!
7
MODULE M1
8
  TYPE T1
9
    INTEGER :: I=7
10
  END TYPE T1
11
CONTAINS
12
  SUBROUTINE S1(I)
13
    INTEGER, INTENT(IN) :: I
14
    TYPE(T1) :: D(1:I)
15
    IF (any (D(:)%I.NE.7)) CALL ABORT()
16
  END SUBROUTINE S1
17
END MODULE M1
18
  USE M1
19
  CALL S1(2)
20
END
21
! { dg-final { cleanup-modules "m1" } }

powered by: WebSVN 2.1.0

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