Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / final02.f90
blobb474f45ee5c327b14b5c2ec6118af5350606b44e
1 !RUN: %flang_fc1 -fsyntax-only %s 2>&1 | FileCheck %s
2 module 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 contains
29 subroutine t1f0(x)
30 type(t1) :: x
31 end subroutine
32 subroutine t1f1(x)
33 type(t1) :: x(:)
34 end subroutine
35 impure elemental subroutine t2fe(x)
36 type(t2), intent(in out) :: x
37 end subroutine
38 subroutine t3far(x)
39 type(t3) :: x(..)
40 end subroutine
41 end module
43 subroutine test ! *not* a main program, since they don't finalize locals
44 use m
45 !CHECK-NOT: 'scalar1' of derived type 't1'
46 type(t1) :: scalar1
47 !CHECK-NOT: 'vector1' of derived type 't1'
48 type(t1) :: vector1(2)
49 !CHECK: 'matrix1' of derived type 't1' does not have a FINAL subroutine for its rank (2)
50 type(t1) :: matrix1(2,2)
51 !CHECK-NOT: 'scalar2' of derived type 't2'
52 type(t2) :: scalar2
53 !CHECK-NOT: 'vector2' of derived type 't2'
54 type(t2) :: vector2(2)
55 !CHECK-NOT: 'matrix2' of derived type 't2'
56 type(t2) :: matrix2(2,2)
57 !CHECK-NOT: 'scalar3' of derived type 't3'
58 type(t3) :: scalar3
59 !CHECK-NOT: 'vector3' of derived type 't3'
60 type(t3) :: vector3(2)
61 !CHECK-NOT: 'matrix3' of derived type 't2'
62 type(t3) :: matrix3(2,2)
63 !CHECK-NOT: 'scalar4' of derived type 't4'
64 type(t4) :: scalar4
65 !CHECK-NOT: 'vector4' of derived type 't4'
66 type(t4) :: vector4(2)
67 !CHECK: 'matrix4' of derived type 't4' extended from 't1' does not have a FINAL subroutine for its rank (2)
68 type(t4) :: matrix4(2,2)
69 end