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

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [extends_9.f03] - Blame information for rev 694

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do compile }
2
!
3
! PR42257: [OOP] Compiler segmentation fault due missing public statement
4
!
5
! Contributed by Oystein Olsen 
6
 
7
MODULE run_example_fortran03
8
  IMPLICIT NONE
9
  PRIVATE
10
  PUBLIC :: epoch
11
 
12
  INTEGER, PARAMETER :: I4B = SELECTED_INT_KIND(9)
13
  INTEGER, PARAMETER :: DP = SELECTED_REAL_KIND(15,307)
14
 
15
  TYPE epoch
16
     INTEGER(I4B) :: i = 2451545
17
     REAL(DP)     :: f = 0.5_DP
18
  END TYPE
19
 
20
  TYPE, EXTENDS(epoch) :: time
21
     REAL(DP) :: t = 0.0_DP
22
  END TYPE
23
END MODULE
24
 
25
 
26
  USE  run_example_fortran03
27
  IMPLICIT NONE
28
 
29
  CLASS(epoch), ALLOCATABLE :: e4
30
 
31
  ALLOCATE(epoch::e4)
32
  WRITE(*,*) e4%i, e4%f
33
 
34
END
35
 
36
! { dg-final { cleanup-modules "run_example_fortran03" } }

powered by: WebSVN 2.1.0

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