annotate gcc/testsuite/gfortran.dg/finalize_6.f90 @ 111:04ced10e8804

gcc 7
author kono
date Fri, 27 Oct 2017 22:46:09 +0900
parents
children
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
rev   line source
111
kono
parents:
diff changeset
1 ! { dg-do compile }
kono
parents:
diff changeset
2 ! { dg-options "-std=f95" }
kono
parents:
diff changeset
3
kono
parents:
diff changeset
4 ! Parsing of finalizer procedure definitions.
kono
parents:
diff changeset
5 ! Check that CONTAINS/FINAL in derived types is rejected for F95.
kono
parents:
diff changeset
6
kono
parents:
diff changeset
7 MODULE final_type
kono
parents:
diff changeset
8 IMPLICIT NONE
kono
parents:
diff changeset
9
kono
parents:
diff changeset
10 TYPE :: mytype
kono
parents:
diff changeset
11 INTEGER :: fooarr(42)
kono
parents:
diff changeset
12 REAL :: foobar
kono
parents:
diff changeset
13 CONTAINS ! { dg-error "Fortran 2003: CONTAINS block in derived type definition" }
kono
parents:
diff changeset
14 FINAL :: finalize_single ! { dg-error "Fortran 2003: FINAL procedure declaration|FINAL procedure 'finalize_single' at .1. is not a SUBROUTINE" }
kono
parents:
diff changeset
15 END TYPE mytype ! { dg-error "Fortran 2008: Derived type definition at .1. with empty CONTAINS section" }
kono
parents:
diff changeset
16
kono
parents:
diff changeset
17 CONTAINS
kono
parents:
diff changeset
18
kono
parents:
diff changeset
19 SUBROUTINE finalize_single (el)
kono
parents:
diff changeset
20 IMPLICIT NONE
kono
parents:
diff changeset
21 TYPE(mytype) :: el
kono
parents:
diff changeset
22 ! Do nothing in this test
kono
parents:
diff changeset
23 END SUBROUTINE finalize_single
kono
parents:
diff changeset
24
kono
parents:
diff changeset
25 END MODULE final_type
kono
parents:
diff changeset
26
kono
parents:
diff changeset
27 PROGRAM finalizer
kono
parents:
diff changeset
28 IMPLICIT NONE
kono
parents:
diff changeset
29 ! Do nothing
kono
parents:
diff changeset
30 END PROGRAM finalizer