3 ! Parsing of finalizer procedure definitions.
4 ! Check parsing of valid finalizer definitions.
10 INTEGER, ALLOCATABLE :: fooarr(:)
13 FINAL :: finalize_single
14 FINAL finalize_vector, finalize_matrix
15 ! TODO: Test with different kind type parameters once they are implemented.
20 ELEMENTAL SUBROUTINE finalize_single (el)
22 TYPE(mytype), INTENT(IN) :: el
23 ! Do nothing in this test
24 END SUBROUTINE finalize_single
26 SUBROUTINE finalize_vector (el)
28 TYPE(mytype), INTENT(INOUT) :: el(:)
29 ! Do nothing in this test
30 END SUBROUTINE finalize_vector
32 SUBROUTINE finalize_matrix (el)
34 TYPE(mytype) :: el(:, :)
35 ! Do nothing in this test
36 END SUBROUTINE finalize_matrix
41 USE final_type, ONLY: mytype
44 TYPE(mytype) :: el, vec(42)
45 TYPE(mytype), ALLOCATABLE :: mat(:, :)