aarch64: Add missing ACLE macro for NEON-SVE Bridge
[official-gcc.git] / gcc / testsuite / gfortran.dg / finalize_53.f90
blobeeacb9eef9c52112ec7f2c7a5203b506f9dcf56e
1 ! { dg-do compile }
3 ! Check that the data reference preliminary code is properly
4 ! generated and accepted by the finalization handling code.
6 module m
7 implicit none
8 type t
9 integer :: i
10 contains
11 final :: finalize_t
12 end type t
13 logical :: finalize_called = .false.
14 contains
15 subroutine finalize_t(a)
16 type(t) :: a
17 finalize_called = .true.
18 end subroutine finalize_t
19 end module m
20 program p
21 use m
22 type u
23 type(t), allocatable :: ta
24 end type u
25 class(u), allocatable :: c(:)
26 integer, allocatable :: a(:), b(:)
27 a = [1, 2, 3]
28 b = [3, 5, 1]
29 allocate(c, source = [u(t(1)), u(t(9))])
30 deallocate(c(count(a + b == 4))%ta)
31 if (.not. allocated (c(1)%ta)) stop 11
32 if (allocated (c(2)%ta)) stop 12
33 if (.not. finalize_called) stop 13
34 end program p