3 ! Parsing of finalizer procedure definitions.
4 ! Check for appropriate errors on invalid final procedures.
10 INTEGER, ALLOCATABLE :: fooarr(:)
12 FINAL :: finalize_matrix ! { dg-error "must be inside a derived type" }
14 FINAL :: ! { dg-error "Empty FINAL" }
15 FINAL ! { dg-error "Empty FINAL" }
16 FINAL :: + ! { dg-error "Expected module procedure name" }
17 FINAL :: iamnot ! { dg-error "is not a SUBROUTINE" }
18 FINAL :: finalize_single finalize_vector ! { dg-error "Expected ','" }
19 FINAL :: finalize_single, finalize_vector
20 FINAL :: finalize_single ! { dg-error "is already defined" }
21 FINAL :: finalize_vector_2 ! { dg-error "has the same rank" }
22 FINAL :: finalize_single_2 ! { dg-error "has the same rank" }
23 FINAL :: bad_function ! { dg-error "is not a SUBROUTINE" }
24 FINAL bad_num_args_1 ! { dg-error "must have exactly one argument" }
25 FINAL bad_num_args_2 ! { dg-error "must have exactly one argument" }
30 FINAL :: bad_intent_out
32 ! TODO: Test for polymorphism, kind parameters once those are implemented.
37 SUBROUTINE finalize_single (el)
40 END SUBROUTINE finalize_single
42 ELEMENTAL SUBROUTINE finalize_single_2 (el)
44 TYPE(mytype), INTENT(IN) :: el
45 END SUBROUTINE finalize_single_2
47 SUBROUTINE finalize_vector (el)
49 TYPE(mytype), INTENT(INOUT) :: el(:)
50 END SUBROUTINE finalize_vector
52 SUBROUTINE finalize_vector_2 (el)
54 TYPE(mytype), INTENT(IN) :: el(:)
55 END SUBROUTINE finalize_vector_2
57 SUBROUTINE finalize_matrix (el)
59 TYPE(mytype) :: el(:, :)
60 END SUBROUTINE finalize_matrix
62 INTEGER FUNCTION bad_function (el)
67 END FUNCTION bad_function
69 SUBROUTINE bad_num_args_1 ()
71 END SUBROUTINE bad_num_args_1
73 SUBROUTINE bad_num_args_2 (el, x)
77 END SUBROUTINE bad_num_args_2
79 SUBROUTINE bad_arg_type (el) ! { dg-error "must be of type 'mytype'" }
82 END SUBROUTINE bad_arg_type
84 SUBROUTINE bad_pointer (el) ! { dg-error "must not be a POINTER" }
86 TYPE(mytype), POINTER :: el
87 END SUBROUTINE bad_pointer
89 SUBROUTINE bad_alloc (el) ! { dg-error "must not be ALLOCATABLE" }
91 TYPE(mytype), ALLOCATABLE :: el(:)
92 END SUBROUTINE bad_alloc
94 SUBROUTINE bad_optional (el) ! { dg-error "must not be OPTIONAL" }
96 TYPE(mytype), OPTIONAL :: el
97 END SUBROUTINE bad_optional
99 SUBROUTINE bad_intent_out (el) ! { dg-error "must not be INTENT\\(OUT\\)" }
101 TYPE(mytype), INTENT(OUT) :: el
102 END SUBROUTINE bad_intent_out
104 END MODULE final_type
108 ! Nothing here, errors above
109 END PROGRAM finalizer
111 ! TODO: Remove this once finalization is implemented.
112 ! { dg-excess-errors "not yet implemented" }
114 ! { dg-final { cleanup-modules "final_type" } }