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

Subversion Repositories openrisc_me

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [finalize_4.f03] - Blame information for rev 377

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 parsing of valid finalizer definitions.
5
 
6
MODULE final_type
7
  IMPLICIT NONE
8
 
9
  TYPE :: mytype
10
    INTEGER, ALLOCATABLE :: fooarr(:)
11
    REAL :: foobar
12
  CONTAINS
13
    FINAL :: finalize_single
14
    FINAL finalize_vector, finalize_matrix
15
    ! TODO:  Test with different kind type parameters once they are implemented.
16
  END TYPE mytype
17
 
18
CONTAINS
19
 
20
  ELEMENTAL SUBROUTINE finalize_single (el)
21
    IMPLICIT NONE
22
    TYPE(mytype), INTENT(IN) :: el
23
    ! Do nothing in this test
24
  END SUBROUTINE finalize_single
25
 
26
  SUBROUTINE finalize_vector (el)
27
    IMPLICIT NONE
28
    TYPE(mytype), INTENT(INOUT) :: el(:)
29
    ! Do nothing in this test
30
  END SUBROUTINE finalize_vector
31
 
32
  SUBROUTINE finalize_matrix (el)
33
    IMPLICIT NONE
34
    TYPE(mytype) :: el(:, :)
35
    ! Do nothing in this test
36
  END SUBROUTINE finalize_matrix
37
 
38
END MODULE final_type
39
 
40
PROGRAM finalizer
41
  USE final_type, ONLY: mytype
42
  IMPLICIT NONE
43
 
44
  TYPE(mytype) :: el, vec(42)
45
  TYPE(mytype), ALLOCATABLE :: mat(:, :)
46
 
47
  ALLOCATE(mat(2, 3))
48
  DEALLOCATE(mat)
49
 
50
END PROGRAM finalizer
51
 
52
! TODO: Remove this once finalization is implemented.
53
! { dg-excess-errors "not yet implemented" }
54
 
55
! { 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.