aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/finalize_7.f03
blob: 5807ed50e15fd9bdd7637e963bc712828a133e1c (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
! { dg-do compile }
! { dg-options "-Wsurprising" }

! Implementation of finalizer procedures.
! Check for expected warnings on dubious FINAL constructs.

MODULE final_type
  IMPLICIT NONE

  TYPE :: type_1
    INTEGER, ALLOCATABLE :: fooarr(:)
    REAL :: foobar
  CONTAINS
    ! Non-scalar procedures should be assumed shape
    FINAL :: fin1_scalar
    FINAL :: fin1_shape_1
    FINAL :: fin1_shape_2
  END TYPE type_1

  TYPE :: type_2 ! { dg-warning "Only array FINAL procedures" }
    REAL :: x
  CONTAINS
    ! No scalar finalizer, only array ones
    FINAL :: fin2_vector
  END TYPE type_2

CONTAINS

  SUBROUTINE fin1_scalar (el)
    IMPLICIT NONE
    TYPE(type_1) :: el
  END SUBROUTINE fin1_scalar

  SUBROUTINE fin1_shape_1 (v) ! { dg-warning "assumed shape" }
    IMPLICIT NONE
    TYPE(type_1) :: v(*)
  END SUBROUTINE fin1_shape_1

  SUBROUTINE fin1_shape_2 (v) ! { dg-warning "assumed shape" }
    IMPLICIT NONE
    TYPE(type_1) :: v(42, 5)
  END SUBROUTINE fin1_shape_2

  SUBROUTINE fin2_vector (v)
    IMPLICIT NONE
    TYPE(type_2) :: v(:)
  END SUBROUTINE fin2_vector

END MODULE final_type

PROGRAM finalizer
  IMPLICIT NONE
  ! Nothing here
END PROGRAM finalizer