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

Subversion Repositories openrisc_2011-10-31

[/] [openrisc/] [tags/] [gnu-src/] [gcc-4.5.1/] [gcc-4.5.1-or32-1.0rc2/] [gcc/] [testsuite/] [gfortran.dg/] [finalize_1.f08] - Blame information for rev 437

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

Line No. Rev Author Line
1 302 jeremybenn
! { dg-do compile }
2
 
3
! Parsing of finalizer procedure definitions.
4
! Check that CONTAINS is allowed in TYPE definition; but empty only for F2008
5
 
6
MODULE final_type
7
  IMPLICIT NONE
8
 
9
  TYPE :: mytype
10
    INTEGER, ALLOCATABLE :: fooarr(:)
11
    REAL :: foobar
12
  CONTAINS
13
  END TYPE mytype
14
 
15
CONTAINS
16
 
17
  SUBROUTINE bar
18
    TYPE :: t
19
    CONTAINS ! This is ok
20
    END TYPE t
21
    ! Nothing
22
  END SUBROUTINE bar
23
 
24
END MODULE final_type
25
 
26
PROGRAM finalizer
27
  IMPLICIT NONE
28
  ! Do nothing here
29
END PROGRAM finalizer
30
 
31
! { dg-final { cleanup-modules "final_type" } }

powered by: WebSVN 2.1.0

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