aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/typebound_call_16.f03
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/typebound_call_16.f03')
-rw-r--r--gcc/testsuite/gfortran.dg/typebound_call_16.f0335
1 files changed, 35 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/typebound_call_16.f03 b/gcc/testsuite/gfortran.dg/typebound_call_16.f03
new file mode 100644
index 00000000000..fdd60c603cc
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/typebound_call_16.f03
@@ -0,0 +1,35 @@
+! { dg-do compile }
+!
+! PR 41685: [OOP] internal compiler error: verify_flow_info failed
+!
+! Contributed by Salvatore Filippone <sfilippone@uniroma2.it>
+
+module base_mat_mod
+
+ type :: base_sparse_mat
+ contains
+ procedure, pass(a) :: get_nrows
+ end type base_sparse_mat
+
+contains
+
+ integer function get_nrows(a)
+ implicit none
+ class(base_sparse_mat), intent(in) :: a
+ end function get_nrows
+
+end module base_mat_mod
+
+
+ use base_mat_mod
+
+ type, extends(base_sparse_mat) :: s_coo_sparse_mat
+ end type s_coo_sparse_mat
+
+ class(s_coo_sparse_mat), pointer :: a
+ Integer :: m
+ m = a%get_nrows()
+
+end
+
+! { dg-final { cleanup-modules "base_mat_mod" } }