Merge from mainline (163495:164578).
[official-gcc/graphite-test-results.git] / gcc / testsuite / gfortran.dg / pointer_check_7.f90
blob0f6dcdc87fc4e188a0955fbcb903406499c69c86
1 ! { dg-do compile }
2 ! { dg-options "-fcheck=pointer" }
4 ! PR 45438: [4.6 Regression] [OOP] ICE with -fcheck=pointer
6 ! Contributed by Salvatore Filippone <sfilippone@uniroma2.it>
8 module base_mat_mod
10 implicit none
12 type :: base_sparse_mat
13 contains
14 procedure :: get_fmt
15 end type
17 contains
19 function get_fmt(a) result(res)
20 class(base_sparse_mat), intent(in) :: a
21 character(len=5) :: res
22 res = 'NULL'
23 end function
25 subroutine errlog(name)
26 character(len=*) :: name
27 end subroutine
29 subroutine test (a)
30 class(base_sparse_mat), intent(in) :: a
31 call errlog(a%get_fmt())
32 end subroutine
34 end module
36 ! { dg-final { cleanup-modules "base_mat_mod" } }