URL
https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk
Subversion Repositories openrisc_me
[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [dynamic_dispatch_5.f03] - Rev 302
Compare with Previous | Blame | View Log
! { dg-do compile }! Tests the fix for PR4164656 in which the call to a%a%scal failed to compile.!! Contributed by Salvatore Filippone <sfilippone@uniroma2.it>!module const_modinteger, parameter :: longndig=12integer, parameter :: long_int_k_ = selected_int_kind(longndig)integer, parameter :: dpk_ = kind(1.d0)integer, parameter :: spk_ = kind(1.e0)end module const_modmodule base_mat_moduse const_modtype :: base_sparse_matinteger, private :: m, ninteger, private :: state, duplicatelogical, private :: triangle, unitd, upper, sortedcontainsprocedure, pass(a) :: get_nzerosend type base_sparse_matprivate :: get_nzeroscontainsfunction get_nzeros(a) result(res)implicit noneclass(base_sparse_mat), intent(in) :: ainteger :: resinteger :: err_actcharacter(len=20) :: name='base_get_nzeros'logical, parameter :: debug=.false.res = -1end function get_nzerosend module base_mat_modmodule s_base_mat_moduse base_mat_modtype, extends(base_sparse_mat) :: s_base_sparse_matcontainsprocedure, pass(a) :: s_scalsprocedure, pass(a) :: s_scalgeneric, public :: scal => s_scals, s_scalend type s_base_sparse_matprivate :: s_scals, s_scaltype, extends(s_base_sparse_mat) :: s_coo_sparse_matinteger :: nnzinteger, allocatable :: ia(:), ja(:)real(spk_), allocatable :: val(:)containsprocedure, pass(a) :: get_nzeros => s_coo_get_nzerosprocedure, pass(a) :: s_scals => s_coo_scalsprocedure, pass(a) :: s_scal => s_coo_scalend type s_coo_sparse_matprivate :: s_coo_scals, s_coo_scal, s_coo_get_nzeroscontainssubroutine s_scals(d,a,info)implicit noneclass(s_base_sparse_mat), intent(in) :: areal(spk_), intent(in) :: dinteger, intent(out) :: infoInteger :: err_actcharacter(len=20) :: name='s_scals'logical, parameter :: debug=.false.! This is the base version. If we get here! it means the derived class is incomplete,! so we throw an error.info = 700end subroutine s_scalssubroutine s_scal(d,a,info)implicit noneclass(s_base_sparse_mat), intent(in) :: areal(spk_), intent(in) :: d(:)integer, intent(out) :: infoInteger :: err_actcharacter(len=20) :: name='s_scal'logical, parameter :: debug=.false.! This is the base version. If we get here! it means the derived class is incomplete,! so we throw an error.info = 700end subroutine s_scalfunction s_coo_get_nzeros(a) result(res)implicit noneclass(s_coo_sparse_mat), intent(in) :: ainteger :: resres = a%nnzend function s_coo_get_nzerossubroutine s_coo_scal(d,a,info)use const_modimplicit noneclass(s_coo_sparse_mat), intent(inout) :: areal(spk_), intent(in) :: d(:)integer, intent(out) :: infoInteger :: err_act,mnm, i, j, mcharacter(len=20) :: name='scal'logical, parameter :: debug=.false.info = 0do i=1,a%get_nzeros()j = a%ia(i)a%val(i) = a%val(i) * d(j)enddoend subroutine s_coo_scalsubroutine s_coo_scals(d,a,info)use const_modimplicit noneclass(s_coo_sparse_mat), intent(inout) :: areal(spk_), intent(in) :: dinteger, intent(out) :: infoInteger :: err_act,mnm, i, j, mcharacter(len=20) :: name='scal'logical, parameter :: debug=.false.info = 0do i=1,a%get_nzeros()a%val(i) = a%val(i) * denddoend subroutine s_coo_scalsend module s_base_mat_modmodule s_mat_moduse s_base_mat_modtype :: s_sparse_matclass(s_base_sparse_mat), pointer :: acontainsprocedure, pass(a) :: s_scalsprocedure, pass(a) :: s_scalgeneric, public :: scal => s_scals, s_scalend type s_sparse_matinterface scalmodule procedure s_scals, s_scalend interfacecontainssubroutine s_scal(d,a,info)use const_modimplicit noneclass(s_sparse_mat), intent(inout) :: areal(spk_), intent(in) :: d(:)integer, intent(out) :: infointeger :: err_actcharacter(len=20) :: name='csnmi'logical, parameter :: debug=.false.print *, "s_scal"call a%a%scal(d,info)returnend subroutine s_scalsubroutine s_scals(d,a,info)use const_modimplicit noneclass(s_sparse_mat), intent(inout) :: areal(spk_), intent(in) :: dinteger, intent(out) :: infointeger :: err_actcharacter(len=20) :: name='csnmi'logical, parameter :: debug=.false.print *, "s_scals"call a%a%scal(d,info)returnend subroutine s_scalsend module s_mat_moduse s_mat_modclass (s_sparse_mat), pointer :: atype (s_sparse_mat), target :: btype (s_base_sparse_mat), target :: cinteger infob%a => ca => bcall a%scal (1.0_spk_, info)end! { dg-final { cleanup-modules "const_mod base_mat_mod s_base_mat_mod s_mat_mod" } }
