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

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [finalize_4.f03] - Rev 694

Compare with Previous | Blame | View Log

! { dg-do compile }

! Parsing of finalizer procedure definitions.
! Check parsing of valid finalizer definitions.

MODULE final_type
  IMPLICIT NONE

  TYPE :: mytype
    INTEGER, ALLOCATABLE :: fooarr(:)
    REAL :: foobar
  CONTAINS
    FINAL :: finalize_single
    FINAL finalize_vector, finalize_matrix
    ! TODO:  Test with different kind type parameters once they are implemented.
  END TYPE mytype

CONTAINS

  ELEMENTAL SUBROUTINE finalize_single (el)
    IMPLICIT NONE
    TYPE(mytype), INTENT(IN) :: el
    ! Do nothing in this test
  END SUBROUTINE finalize_single

  SUBROUTINE finalize_vector (el)
    IMPLICIT NONE
    TYPE(mytype), INTENT(INOUT) :: el(:)
    ! Do nothing in this test
  END SUBROUTINE finalize_vector

  SUBROUTINE finalize_matrix (el)
    IMPLICIT NONE
    TYPE(mytype) :: el(:, :)
    ! Do nothing in this test
  END SUBROUTINE finalize_matrix

END MODULE final_type

PROGRAM finalizer
  USE final_type, ONLY: mytype
  IMPLICIT NONE

  TYPE(mytype) :: el, vec(42)
  TYPE(mytype), ALLOCATABLE :: mat(:, :)

  ALLOCATE(mat(2, 3))
  DEALLOCATE(mat)

END PROGRAM finalizer

! TODO: Remove this once finalization is implemented.
! { dg-excess-errors "not yet implemented" }

! { dg-final { cleanup-modules "final_type" } }

Compare with Previous | Blame | View Log

powered by: WebSVN 2.1.0

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