modula2: Simplify REAL/LONGREAL/SHORTREAL node creation.
[official-gcc.git] / gcc / testsuite / gfortran.dg / typebound_call_16.f03
blob39831957aa81ccc3767255cee293f85af501c6ae
1 ! { dg-do compile }
3 ! PR 41685: [OOP] internal compiler error: verify_flow_info failed
5 ! Contributed by Salvatore Filippone <sfilippone@uniroma2.it>
7 module base_mat_mod
9   type  :: base_sparse_mat
10   contains 
11     procedure, pass(a) :: get_nrows
12   end type base_sparse_mat
13   
14 contains
16   integer function get_nrows(a)
17     implicit none 
18     class(base_sparse_mat), intent(in) :: a
19   end function get_nrows
21 end module  base_mat_mod
24   use base_mat_mod
26   type, extends(base_sparse_mat) :: s_coo_sparse_mat
27   end type s_coo_sparse_mat
29   class(s_coo_sparse_mat), pointer :: a
30   Integer :: m
31   m = a%get_nrows()
33 end