xref: /llvm-project/flang/test/Semantics/final02.f90 (revision 338e312503d41c90b6d227227bc23cc6c7537936)
1!RUN: %flang_fc1 -fsyntax-only %s 2>&1 | FileCheck %s
2module m
3  type :: t1
4    integer :: n
5   contains
6    final :: t1f0, t1f1
7  end type
8  type :: t2
9    integer :: n
10   contains
11    final :: t2fe
12  end type
13  type :: t3
14    integer :: n
15   contains
16    final :: t3far
17  end type
18  type, extends(t1) :: t4
19  end type
20  type :: t5
21    !CHECK-NOT: 'scalar' of derived type 't1'
22    type(t1) :: scalar
23    !CHECK-NOT: 'vector' of derived type 't1'
24    type(t1) :: vector(2)
25    !CHECK: 'matrix' of derived type 't1' does not have a FINAL subroutine for its rank (2)
26    type(t1) :: matrix(2, 2)
27  end type
28  type :: t6
29    integer :: n
30   contains
31    final :: t6f3
32  end type
33 contains
34  subroutine t1f0(x)
35    type(t1) :: x
36  end subroutine
37  subroutine t1f1(x)
38    type(t1) :: x(:)
39  end subroutine
40  impure elemental subroutine t2fe(x)
41    type(t2), intent(in out) :: x
42  end subroutine
43  subroutine t3far(x)
44    type(t3) :: x(..)
45  end subroutine
46  subroutine t6f3(x)
47    type(t6) :: x(:,:,:)
48  end subroutine
49end module
50
51subroutine test(assumedRank) ! *not* a main program, since they don't finalize locals
52  use m
53  !CHECK-NOT: 'scalar1' of derived type 't1'
54  type(t1) :: scalar1
55  !CHECK-NOT: 'vector1' of derived type 't1'
56  type(t1) :: vector1(2)
57  !CHECK: 'matrix1' of derived type 't1' does not have a FINAL subroutine for its rank (2)
58  type(t1) :: matrix1(2,2)
59  !CHECK-NOT: 'scalar2' of derived type 't2'
60  type(t2) :: scalar2
61  !CHECK-NOT: 'vector2' of derived type 't2'
62  type(t2) :: vector2(2)
63  !CHECK-NOT: 'matrix2' of derived type 't2'
64  type(t2) :: matrix2(2,2)
65  !CHECK-NOT: 'scalar3' of derived type 't3'
66  type(t3) :: scalar3
67  !CHECK-NOT: 'vector3' of derived type 't3'
68  type(t3) :: vector3(2)
69  !CHECK-NOT: 'matrix3' of derived type 't2'
70  type(t3) :: matrix3(2,2)
71  !CHECK-NOT: 'scalar4' of derived type 't4'
72  type(t4) :: scalar4
73  !CHECK-NOT: 'vector4' of derived type 't4'
74  type(t4) :: vector4(2)
75  !CHECK: 'matrix4' of derived type 't4' extended from 't1' does not have a FINAL subroutine for its rank (2)
76  type(t4) :: matrix4(2,2)
77  !CHECK-NOT: 'assumedRank' of derived type 't6'
78  type(t6) :: assumedRank(..)
79end
80