PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / finalize_25.f90
blob20137b46b64b40a18e92e03b8aa955bcec08f7e6
1 ! { dg-do run }
3 ! PR fortran/58880
4 ! PR fortran/60495
6 ! Contributed by Andrew Benson and Janus Weil
9 module gn
10 implicit none
11 type sl
12 integer, allocatable, dimension(:) :: lv
13 contains
14 final :: sld
15 end type
16 type :: nde
17 type(sl) :: r
18 end type nde
20 integer :: cnt = 0
22 contains
24 subroutine sld(s)
25 type(sl) :: s
26 cnt = cnt + 1
27 ! print *,'Finalize sl'
28 end subroutine
29 subroutine ndm(s)
30 type(nde), intent(inout) :: s
31 type(nde) :: i
32 i=s
33 end subroutine ndm
34 end module
36 program main
37 use gn
38 type :: nde2
39 type(sl) :: r
40 end type nde2
41 type(nde) :: x
43 cnt = 0
44 call ndm(x)
45 if (cnt /= 2) STOP 1
47 cnt = 0
48 call ndm2()
49 if (cnt /= 3) STOP 2
50 contains
51 subroutine ndm2
52 type(nde2) :: s,i
53 i=s
54 end subroutine ndm2
55 end program main