2011-05-23 Tom de Vries <tom@codesourcery.com>
[official-gcc.git] / gcc / testsuite / gfortran.dg / finalize_4.f03
blob6e99256c252443eff6abd86187c87c49e647535f
1 ! { dg-do compile }
3 ! Parsing of finalizer procedure definitions.
4 ! Check parsing of valid finalizer definitions.
6 MODULE final_type
7   IMPLICIT NONE
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
18 CONTAINS
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
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
32   SUBROUTINE finalize_matrix (el)
33     IMPLICIT NONE
34     TYPE(mytype) :: el(:, :)
35     ! Do nothing in this test
36   END SUBROUTINE finalize_matrix
38 END MODULE final_type
40 PROGRAM finalizer
41   USE final_type, ONLY: mytype
42   IMPLICIT NONE
44   TYPE(mytype) :: el, vec(42)
45   TYPE(mytype), ALLOCATABLE :: mat(:, :)
47   ALLOCATE(mat(2, 3))
48   DEALLOCATE(mat)
50 END PROGRAM finalizer
52 ! TODO: Remove this once finalization is implemented.
53 ! { dg-excess-errors "not yet implemented" }
55 ! { dg-final { cleanup-modules "final_type" } }