aarch64: Add vector floating point extend pattern [PR113880, PR113869]
[official-gcc.git] / gcc / testsuite / gfortran.dg / finalize_1.f08
blob391a0f13efad21b6130189be4c78150b882162ba
1 ! { dg-do compile }
3 ! Parsing of finalizer procedure definitions.
4 ! Check that CONTAINS is allowed in TYPE definition; but empty only for F2008
6 MODULE final_type
7   IMPLICIT NONE
9   TYPE :: mytype
10     INTEGER, ALLOCATABLE :: fooarr(:)
11     REAL :: foobar
12   CONTAINS
13   END TYPE mytype
15 CONTAINS
16   
17   SUBROUTINE bar
18     TYPE :: t
19     CONTAINS ! This is ok
20     END TYPE t
21     ! Nothing
22   END SUBROUTINE bar
24 END MODULE final_type
26 PROGRAM finalizer
27   IMPLICIT NONE
28   ! Do nothing here
29 END PROGRAM finalizer