[to-be-committed] [RISC-V] Use Zbkb for general 64 bit constants when profitable
[official-gcc.git] / gcc / testsuite / gfortran.dg / finalize_8.f03
blobb7fa10dda3135b374118255f1c76514601090e20
1 ! { dg-do run }
3 ! PR97122: Declaration of a finalizable derived type in a submodule
4 ! IS allowed.
6 ! Contributed by Ian Harvey  <ian_harvey@bigpond.com>
8 MODULE m
9   IMPLICIT NONE
11   INTERFACE
12     MODULE SUBROUTINE other(i)
13       IMPLICIT NONE
14       integer, intent(inout) :: i
15     END SUBROUTINE other
16   END INTERFACE
18   integer :: mi
20 END MODULE m
22 SUBMODULE (m) s
23   IMPLICIT NONE
25   TYPE :: t
26     integer :: i
27   CONTAINS
28     FINAL :: final_t  ! Used to be an error here
29   END TYPE t
31 CONTAINS
33   SUBROUTINE final_t(arg)
34     TYPE(t), INTENT(INOUT) :: arg
35     mi = -arg%i
36   END SUBROUTINE final_t
38   module subroutine other(i)  ! 'ti' is finalized
39     integer, intent(inout) :: i
40     type(t) :: ti
41     ti%i = i
42   END subroutine other
43 END SUBMODULE s
45   use m
46   integer :: i = 42
47   call other(i)
48   if (mi .ne. -i) stop 1
49 end