111
|
1 ! { dg-do compile }
|
|
2 ! { dg-options "-std=f95" }
|
|
3
|
|
4 ! Parsing of finalizer procedure definitions.
|
|
5 ! Check that CONTAINS/FINAL in derived types is rejected for F95.
|
|
6
|
|
7 MODULE final_type
|
|
8 IMPLICIT NONE
|
|
9
|
|
10 TYPE :: mytype
|
|
11 INTEGER :: fooarr(42)
|
|
12 REAL :: foobar
|
|
13 CONTAINS ! { dg-error "Fortran 2003: CONTAINS block in derived type definition" }
|
|
14 FINAL :: finalize_single ! { dg-error "Fortran 2003: FINAL procedure declaration|FINAL procedure 'finalize_single' at .1. is not a SUBROUTINE" }
|
|
15 END TYPE mytype ! { dg-error "Fortran 2008: Derived type definition at .1. with empty CONTAINS section" }
|
|
16
|
|
17 CONTAINS
|
|
18
|
|
19 SUBROUTINE finalize_single (el)
|
|
20 IMPLICIT NONE
|
|
21 TYPE(mytype) :: el
|
|
22 ! Do nothing in this test
|
|
23 END SUBROUTINE finalize_single
|
|
24
|
|
25 END MODULE final_type
|
|
26
|
|
27 PROGRAM finalizer
|
|
28 IMPLICIT NONE
|
|
29 ! Do nothing
|
|
30 END PROGRAM finalizer
|