Fixed inheritance and setup of aggregators.

stopcriterion
Salvatore Filippone 7 years ago
parent f131e0d86d
commit 13dc383079

@ -99,20 +99,20 @@ mld_c_onelev_mod.o: mld_c_base_smoother_mod.o mld_c_dec_aggregator_mod.o
mld_z_onelev_mod.o: mld_z_base_smoother_mod.o mld_z_dec_aggregator_mod.o mld_z_onelev_mod.o: mld_z_base_smoother_mod.o mld_z_dec_aggregator_mod.o
mld_s_base_aggregator_mod.o: mld_base_prec_type.o mld_s_base_aggregator_mod.o: mld_base_prec_type.o
mld_s_hybrid_aggregator_mod.o mld_s_dec_aggregator_mod.o: mld_s_base_aggregator_mod.o mld_s_dec_aggregator_mod.o: mld_s_base_aggregator_mod.o
mld_s_symdec_aggregator_mod.o: mld_s_dec_aggregator_mod.o mld_s_hybrid_aggregator_mod.o mld_s_symdec_aggregator_mod.o: mld_s_dec_aggregator_mod.o
mld_d_base_aggregator_mod.o: mld_base_prec_type.o mld_d_base_aggregator_mod.o: mld_base_prec_type.o
mld_d_hybrid_aggregator_mod.o mld_d_dec_aggregator_mod.o: mld_d_base_aggregator_mod.o mld_d_dec_aggregator_mod.o: mld_d_base_aggregator_mod.o
mld_d_symdec_aggregator_mod.o: mld_d_dec_aggregator_mod.o mld_d_hybrid_aggregator_mod.o mld_d_symdec_aggregator_mod.o: mld_d_dec_aggregator_mod.o
mld_c_base_aggregator_mod.o: mld_base_prec_type.o mld_c_base_aggregator_mod.o: mld_base_prec_type.o
mld_c_hybrid_aggregator_mod.o mld_c_dec_aggregator_mod.o: mld_c_base_aggregator_mod.o mld_c_dec_aggregator_mod.o: mld_c_base_aggregator_mod.o
mld_c_symdec_aggregator_mod.o: mld_c_dec_aggregator_mod.o mld_c_hybrid_aggregator_mod.o mld_c_symdec_aggregator_mod.o: mld_c_dec_aggregator_mod.o
mld_z_base_aggregator_mod.o: mld_base_prec_type.o mld_z_base_aggregator_mod.o: mld_base_prec_type.o
mld_z_hybrid_aggregator_mod.o mld_z_dec_aggregator_mod.o: mld_z_base_aggregator_mod.o mld_z_dec_aggregator_mod.o: mld_z_base_aggregator_mod.o
mld_z_symdec_aggregator_mod.o: mld_z_dec_aggregator_mod.o mld_z_hybrid_aggregator_mod.o mld_z_symdec_aggregator_mod.o: mld_z_dec_aggregator_mod.o
mld_s_base_smoother_mod.o: mld_s_base_solver_mod.o mld_s_base_smoother_mod.o: mld_s_base_solver_mod.o
mld_d_base_smoother_mod.o: mld_d_base_solver_mod.o mld_d_base_smoother_mod.o: mld_d_base_solver_mod.o

@ -200,8 +200,8 @@ subroutine mld_c_base_onelev_cseti(lv,what,val,info,pos)
allocate(mld_c_dec_aggregator_type :: lv%aggr, stat=info) allocate(mld_c_dec_aggregator_type :: lv%aggr, stat=info)
case(mld_sym_dec_aggr_) case(mld_sym_dec_aggr_)
allocate(mld_c_symdec_aggregator_type :: lv%aggr, stat=info) allocate(mld_c_symdec_aggregator_type :: lv%aggr, stat=info)
case(mld_hybrid_aggr_) !!$ case(mld_hybrid_aggr_)
allocate(mld_c_hybrid_aggregator_type :: lv%aggr, stat=info) !!$ allocate(mld_c_hybrid_aggregator_type :: lv%aggr, stat=info)
case default case default
info = psb_err_internal_error_ info = psb_err_internal_error_
end select end select

@ -35,7 +35,7 @@
! POSSIBILITY OF SUCH DAMAGE. ! POSSIBILITY OF SUCH DAMAGE.
! !
! !
subroutine mld_c_base_onelev_setag(lev,val,info,pos) subroutine mld_c_base_onelev_setag(lv,val,info,pos)
use psb_base_mod use psb_base_mod
use mld_c_onelev_mod, mld_protect_name => mld_c_base_onelev_setag use mld_c_onelev_mod, mld_protect_name => mld_c_base_onelev_setag
@ -43,7 +43,7 @@ subroutine mld_c_base_onelev_setag(lev,val,info,pos)
implicit none implicit none
! Arguments ! Arguments
class(mld_c_onelev_type), target, intent(inout) :: lev class(mld_c_onelev_type), target, intent(inout) :: lv
class(mld_c_base_aggregator_type), intent(in) :: val class(mld_c_base_aggregator_type), intent(in) :: val
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
character(len=*), optional, intent(in) :: pos character(len=*), optional, intent(in) :: pos
@ -56,10 +56,10 @@ subroutine mld_c_base_onelev_setag(lev,val,info,pos)
! Ignore pos for aggregator ! Ignore pos for aggregator
if (allocated(lev%aggr)) then if (allocated(lv%aggr)) then
if (.not.same_type_as(lev%aggr,val)) then if (.not.same_type_as(lv%aggr,val)) then
call lev%aggr%free(info) call lv%aggr%free(info)
deallocate(lev%aggr,stat=info) deallocate(lv%aggr,stat=info)
if (info /= 0) then if (info /= 0) then
info = 3111 info = 3111
return return
@ -67,14 +67,14 @@ subroutine mld_c_base_onelev_setag(lev,val,info,pos)
end if end if
end if end if
if (.not.allocated(lev%aggr)) then if (.not.allocated(lv%aggr)) then
allocate(lev%aggr,mold=val,stat=info) allocate(lv%aggr,mold=val,stat=info)
if (info /= 0) then if (info /= 0) then
info = 3111 info = 3111
return return
end if end if
lv%parms%par_aggr_alg = mld_ext_aggr_ lv%parms%par_aggr_alg = mld_ext_aggr_
lv%parms%aggr_type = mld_ext_noalg_ lv%parms%aggr_type = mld_noalg_
end if end if
end subroutine mld_c_base_onelev_setag end subroutine mld_c_base_onelev_setag

@ -200,8 +200,8 @@ subroutine mld_c_base_onelev_seti(lv,what,val,info,pos)
allocate(mld_c_dec_aggregator_type :: lv%aggr, stat=info) allocate(mld_c_dec_aggregator_type :: lv%aggr, stat=info)
case(mld_sym_dec_aggr_) case(mld_sym_dec_aggr_)
allocate(mld_c_symdec_aggregator_type :: lv%aggr, stat=info) allocate(mld_c_symdec_aggregator_type :: lv%aggr, stat=info)
case(mld_hybrid_aggr_) !!$ case(mld_hybrid_aggr_)
allocate(mld_c_hybrid_aggregator_type :: lv%aggr, stat=info) !!$ allocate(mld_c_hybrid_aggregator_type :: lv%aggr, stat=info)
case default case default
info = psb_err_internal_error_ info = psb_err_internal_error_
end select end select

@ -220,8 +220,8 @@ subroutine mld_d_base_onelev_cseti(lv,what,val,info,pos)
allocate(mld_d_dec_aggregator_type :: lv%aggr, stat=info) allocate(mld_d_dec_aggregator_type :: lv%aggr, stat=info)
case(mld_sym_dec_aggr_) case(mld_sym_dec_aggr_)
allocate(mld_d_symdec_aggregator_type :: lv%aggr, stat=info) allocate(mld_d_symdec_aggregator_type :: lv%aggr, stat=info)
case(mld_hybrid_aggr_) !!$ case(mld_hybrid_aggr_)
allocate(mld_d_hybrid_aggregator_type :: lv%aggr, stat=info) !!$ allocate(mld_d_hybrid_aggregator_type :: lv%aggr, stat=info)
case default case default
info = psb_err_internal_error_ info = psb_err_internal_error_
end select end select

@ -35,7 +35,7 @@
! POSSIBILITY OF SUCH DAMAGE. ! POSSIBILITY OF SUCH DAMAGE.
! !
! !
subroutine mld_d_base_onelev_setag(lev,val,info,pos) subroutine mld_d_base_onelev_setag(lv,val,info,pos)
use psb_base_mod use psb_base_mod
use mld_d_onelev_mod, mld_protect_name => mld_d_base_onelev_setag use mld_d_onelev_mod, mld_protect_name => mld_d_base_onelev_setag
@ -43,7 +43,7 @@ subroutine mld_d_base_onelev_setag(lev,val,info,pos)
implicit none implicit none
! Arguments ! Arguments
class(mld_d_onelev_type), target, intent(inout) :: lev class(mld_d_onelev_type), target, intent(inout) :: lv
class(mld_d_base_aggregator_type), intent(in) :: val class(mld_d_base_aggregator_type), intent(in) :: val
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
character(len=*), optional, intent(in) :: pos character(len=*), optional, intent(in) :: pos
@ -56,10 +56,10 @@ subroutine mld_d_base_onelev_setag(lev,val,info,pos)
! Ignore pos for aggregator ! Ignore pos for aggregator
if (allocated(lev%aggr)) then if (allocated(lv%aggr)) then
if (.not.same_type_as(lev%aggr,val)) then if (.not.same_type_as(lv%aggr,val)) then
call lev%aggr%free(info) call lv%aggr%free(info)
deallocate(lev%aggr,stat=info) deallocate(lv%aggr,stat=info)
if (info /= 0) then if (info /= 0) then
info = 3111 info = 3111
return return
@ -67,14 +67,14 @@ subroutine mld_d_base_onelev_setag(lev,val,info,pos)
end if end if
end if end if
if (.not.allocated(lev%aggr)) then if (.not.allocated(lv%aggr)) then
allocate(lev%aggr,mold=val,stat=info) allocate(lv%aggr,mold=val,stat=info)
if (info /= 0) then if (info /= 0) then
info = 3111 info = 3111
return return
end if end if
lv%parms%par_aggr_alg = mld_ext_aggr_ lv%parms%par_aggr_alg = mld_ext_aggr_
lv%parms%aggr_type = mld_ext_noalg_ lv%parms%aggr_type = mld_noalg_
end if end if
end subroutine mld_d_base_onelev_setag end subroutine mld_d_base_onelev_setag

@ -220,8 +220,8 @@ subroutine mld_d_base_onelev_seti(lv,what,val,info,pos)
allocate(mld_d_dec_aggregator_type :: lv%aggr, stat=info) allocate(mld_d_dec_aggregator_type :: lv%aggr, stat=info)
case(mld_sym_dec_aggr_) case(mld_sym_dec_aggr_)
allocate(mld_d_symdec_aggregator_type :: lv%aggr, stat=info) allocate(mld_d_symdec_aggregator_type :: lv%aggr, stat=info)
case(mld_hybrid_aggr_) !!$ case(mld_hybrid_aggr_)
allocate(mld_d_hybrid_aggregator_type :: lv%aggr, stat=info) !!$ allocate(mld_d_hybrid_aggregator_type :: lv%aggr, stat=info)
case default case default
info = psb_err_internal_error_ info = psb_err_internal_error_
end select end select

@ -200,8 +200,8 @@ subroutine mld_s_base_onelev_cseti(lv,what,val,info,pos)
allocate(mld_s_dec_aggregator_type :: lv%aggr, stat=info) allocate(mld_s_dec_aggregator_type :: lv%aggr, stat=info)
case(mld_sym_dec_aggr_) case(mld_sym_dec_aggr_)
allocate(mld_s_symdec_aggregator_type :: lv%aggr, stat=info) allocate(mld_s_symdec_aggregator_type :: lv%aggr, stat=info)
case(mld_hybrid_aggr_) !!$ case(mld_hybrid_aggr_)
allocate(mld_s_hybrid_aggregator_type :: lv%aggr, stat=info) !!$ allocate(mld_s_hybrid_aggregator_type :: lv%aggr, stat=info)
case default case default
info = psb_err_internal_error_ info = psb_err_internal_error_
end select end select

@ -35,7 +35,7 @@
! POSSIBILITY OF SUCH DAMAGE. ! POSSIBILITY OF SUCH DAMAGE.
! !
! !
subroutine mld_s_base_onelev_setag(lev,val,info,pos) subroutine mld_s_base_onelev_setag(lv,val,info,pos)
use psb_base_mod use psb_base_mod
use mld_s_onelev_mod, mld_protect_name => mld_s_base_onelev_setag use mld_s_onelev_mod, mld_protect_name => mld_s_base_onelev_setag
@ -43,7 +43,7 @@ subroutine mld_s_base_onelev_setag(lev,val,info,pos)
implicit none implicit none
! Arguments ! Arguments
class(mld_s_onelev_type), target, intent(inout) :: lev class(mld_s_onelev_type), target, intent(inout) :: lv
class(mld_s_base_aggregator_type), intent(in) :: val class(mld_s_base_aggregator_type), intent(in) :: val
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
character(len=*), optional, intent(in) :: pos character(len=*), optional, intent(in) :: pos
@ -56,10 +56,10 @@ subroutine mld_s_base_onelev_setag(lev,val,info,pos)
! Ignore pos for aggregator ! Ignore pos for aggregator
if (allocated(lev%aggr)) then if (allocated(lv%aggr)) then
if (.not.same_type_as(lev%aggr,val)) then if (.not.same_type_as(lv%aggr,val)) then
call lev%aggr%free(info) call lv%aggr%free(info)
deallocate(lev%aggr,stat=info) deallocate(lv%aggr,stat=info)
if (info /= 0) then if (info /= 0) then
info = 3111 info = 3111
return return
@ -67,14 +67,14 @@ subroutine mld_s_base_onelev_setag(lev,val,info,pos)
end if end if
end if end if
if (.not.allocated(lev%aggr)) then if (.not.allocated(lv%aggr)) then
allocate(lev%aggr,mold=val,stat=info) allocate(lv%aggr,mold=val,stat=info)
if (info /= 0) then if (info /= 0) then
info = 3111 info = 3111
return return
end if end if
lv%parms%par_aggr_alg = mld_ext_aggr_ lv%parms%par_aggr_alg = mld_ext_aggr_
lv%parms%aggr_type = mld_ext_noalg_ lv%parms%aggr_type = mld_noalg_
end if end if
end subroutine mld_s_base_onelev_setag end subroutine mld_s_base_onelev_setag

@ -200,8 +200,8 @@ subroutine mld_s_base_onelev_seti(lv,what,val,info,pos)
allocate(mld_s_dec_aggregator_type :: lv%aggr, stat=info) allocate(mld_s_dec_aggregator_type :: lv%aggr, stat=info)
case(mld_sym_dec_aggr_) case(mld_sym_dec_aggr_)
allocate(mld_s_symdec_aggregator_type :: lv%aggr, stat=info) allocate(mld_s_symdec_aggregator_type :: lv%aggr, stat=info)
case(mld_hybrid_aggr_) !!$ case(mld_hybrid_aggr_)
allocate(mld_s_hybrid_aggregator_type :: lv%aggr, stat=info) !!$ allocate(mld_s_hybrid_aggregator_type :: lv%aggr, stat=info)
case default case default
info = psb_err_internal_error_ info = psb_err_internal_error_
end select end select

@ -220,8 +220,8 @@ subroutine mld_z_base_onelev_cseti(lv,what,val,info,pos)
allocate(mld_z_dec_aggregator_type :: lv%aggr, stat=info) allocate(mld_z_dec_aggregator_type :: lv%aggr, stat=info)
case(mld_sym_dec_aggr_) case(mld_sym_dec_aggr_)
allocate(mld_z_symdec_aggregator_type :: lv%aggr, stat=info) allocate(mld_z_symdec_aggregator_type :: lv%aggr, stat=info)
case(mld_hybrid_aggr_) !!$ case(mld_hybrid_aggr_)
allocate(mld_z_hybrid_aggregator_type :: lv%aggr, stat=info) !!$ allocate(mld_z_hybrid_aggregator_type :: lv%aggr, stat=info)
case default case default
info = psb_err_internal_error_ info = psb_err_internal_error_
end select end select

@ -35,7 +35,7 @@
! POSSIBILITY OF SUCH DAMAGE. ! POSSIBILITY OF SUCH DAMAGE.
! !
! !
subroutine mld_z_base_onelev_setag(lev,val,info,pos) subroutine mld_z_base_onelev_setag(lv,val,info,pos)
use psb_base_mod use psb_base_mod
use mld_z_onelev_mod, mld_protect_name => mld_z_base_onelev_setag use mld_z_onelev_mod, mld_protect_name => mld_z_base_onelev_setag
@ -43,7 +43,7 @@ subroutine mld_z_base_onelev_setag(lev,val,info,pos)
implicit none implicit none
! Arguments ! Arguments
class(mld_z_onelev_type), target, intent(inout) :: lev class(mld_z_onelev_type), target, intent(inout) :: lv
class(mld_z_base_aggregator_type), intent(in) :: val class(mld_z_base_aggregator_type), intent(in) :: val
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
character(len=*), optional, intent(in) :: pos character(len=*), optional, intent(in) :: pos
@ -56,10 +56,10 @@ subroutine mld_z_base_onelev_setag(lev,val,info,pos)
! Ignore pos for aggregator ! Ignore pos for aggregator
if (allocated(lev%aggr)) then if (allocated(lv%aggr)) then
if (.not.same_type_as(lev%aggr,val)) then if (.not.same_type_as(lv%aggr,val)) then
call lev%aggr%free(info) call lv%aggr%free(info)
deallocate(lev%aggr,stat=info) deallocate(lv%aggr,stat=info)
if (info /= 0) then if (info /= 0) then
info = 3111 info = 3111
return return
@ -67,14 +67,14 @@ subroutine mld_z_base_onelev_setag(lev,val,info,pos)
end if end if
end if end if
if (.not.allocated(lev%aggr)) then if (.not.allocated(lv%aggr)) then
allocate(lev%aggr,mold=val,stat=info) allocate(lv%aggr,mold=val,stat=info)
if (info /= 0) then if (info /= 0) then
info = 3111 info = 3111
return return
end if end if
lv%parms%par_aggr_alg = mld_ext_aggr_ lv%parms%par_aggr_alg = mld_ext_aggr_
lv%parms%aggr_type = mld_ext_noalg_ lv%parms%aggr_type = mld_noalg_
end if end if
end subroutine mld_z_base_onelev_setag end subroutine mld_z_base_onelev_setag

@ -220,8 +220,8 @@ subroutine mld_z_base_onelev_seti(lv,what,val,info,pos)
allocate(mld_z_dec_aggregator_type :: lv%aggr, stat=info) allocate(mld_z_dec_aggregator_type :: lv%aggr, stat=info)
case(mld_sym_dec_aggr_) case(mld_sym_dec_aggr_)
allocate(mld_z_symdec_aggregator_type :: lv%aggr, stat=info) allocate(mld_z_symdec_aggregator_type :: lv%aggr, stat=info)
case(mld_hybrid_aggr_) !!$ case(mld_hybrid_aggr_)
allocate(mld_z_hybrid_aggregator_type :: lv%aggr, stat=info) !!$ allocate(mld_z_hybrid_aggregator_type :: lv%aggr, stat=info)
case default case default
info = psb_err_internal_error_ info = psb_err_internal_error_
end select end select

@ -92,7 +92,7 @@ module mld_c_dec_aggregator_mod
type, extends(mld_c_base_aggregator_type) :: mld_c_dec_aggregator_type type, extends(mld_c_base_aggregator_type) :: mld_c_dec_aggregator_type
contains contains
procedure, pass(ag) :: tprol => mld_c_dec_aggregator_build_tprol procedure, pass(ag) :: bld_tprol => mld_c_dec_aggregator_build_tprol
procedure, pass(ag) :: mat_asb => mld_c_dec_aggregator_mat_asb procedure, pass(ag) :: mat_asb => mld_c_dec_aggregator_mat_asb
procedure, nopass :: fmt => mld_c_dec_aggregator_fmt procedure, nopass :: fmt => mld_c_dec_aggregator_fmt
end type mld_c_dec_aggregator_type end type mld_c_dec_aggregator_type

@ -47,7 +47,7 @@
! !
module mld_c_hybrid_aggregator_mod module mld_c_hybrid_aggregator_mod
use mld_c_base_aggregator_mod use mld_c_dec_aggregator_mod
! !
! sm - class(mld_T_base_smoother_type), allocatable ! sm - class(mld_T_base_smoother_type), allocatable
! The current level preconditioner (aka smoother). ! The current level preconditioner (aka smoother).
@ -88,15 +88,10 @@ module mld_c_hybrid_aggregator_mod
! get_nzeros - Number of nonzeros ! get_nzeros - Number of nonzeros
! !
! !
type, extends(mld_c_base_aggregator_type) :: mld_c_hybrid_aggregator_type type, extends(mld_c_dec_aggregator_type) :: mld_c_hybrid_aggregator_type
contains contains
procedure, pass(ag) :: bld_tprol => mld_c_hybrid_aggregator_build_tprol procedure, pass(ag) :: bld_tprol => mld_c_hybrid_aggregator_build_tprol
!!$ procedure, pass(ag) :: mat_asb => mld_c_base_aggregator_mat_asb
!!$ procedure, pass(ag) :: update_level => mld_c_base_aggregator_update_level
!!$ procedure, pass(ag) :: clone => mld_c_base_aggregator_clone
!!$ procedure, pass(ag) :: free => mld_c_base_aggregator_free
!!$ procedure, pass(ag) :: default => mld_c_base_aggregator_default
procedure, nopass :: fmt => mld_c_hybrid_aggregator_fmt procedure, nopass :: fmt => mld_c_hybrid_aggregator_fmt
end type mld_c_hybrid_aggregator_type end type mld_c_hybrid_aggregator_type

@ -94,7 +94,7 @@ module mld_c_symdec_aggregator_mod
type, extends(mld_c_dec_aggregator_type) :: mld_c_symdec_aggregator_type type, extends(mld_c_dec_aggregator_type) :: mld_c_symdec_aggregator_type
contains contains
procedure, pass(ag) :: tprol => mld_c_symdec_aggregator_build_tprol procedure, pass(ag) :: bld_tprol => mld_c_symdec_aggregator_build_tprol
procedure, nopass :: fmt => mld_c_symdec_aggregator_fmt procedure, nopass :: fmt => mld_c_symdec_aggregator_fmt
end type mld_c_symdec_aggregator_type end type mld_c_symdec_aggregator_type

@ -92,7 +92,7 @@ module mld_d_dec_aggregator_mod
type, extends(mld_d_base_aggregator_type) :: mld_d_dec_aggregator_type type, extends(mld_d_base_aggregator_type) :: mld_d_dec_aggregator_type
contains contains
procedure, pass(ag) :: tprol => mld_d_dec_aggregator_build_tprol procedure, pass(ag) :: bld_tprol => mld_d_dec_aggregator_build_tprol
procedure, pass(ag) :: mat_asb => mld_d_dec_aggregator_mat_asb procedure, pass(ag) :: mat_asb => mld_d_dec_aggregator_mat_asb
procedure, nopass :: fmt => mld_d_dec_aggregator_fmt procedure, nopass :: fmt => mld_d_dec_aggregator_fmt
end type mld_d_dec_aggregator_type end type mld_d_dec_aggregator_type

@ -47,7 +47,7 @@
! !
module mld_d_hybrid_aggregator_mod module mld_d_hybrid_aggregator_mod
use mld_d_base_aggregator_mod use mld_d_dec_aggregator_mod
! !
! sm - class(mld_T_base_smoother_type), allocatable ! sm - class(mld_T_base_smoother_type), allocatable
! The current level preconditioner (aka smoother). ! The current level preconditioner (aka smoother).
@ -88,15 +88,10 @@ module mld_d_hybrid_aggregator_mod
! get_nzeros - Number of nonzeros ! get_nzeros - Number of nonzeros
! !
! !
type, extends(mld_d_base_aggregator_type) :: mld_d_hybrid_aggregator_type type, extends(mld_d_dec_aggregator_type) :: mld_d_hybrid_aggregator_type
contains contains
procedure, pass(ag) :: bld_tprol => mld_d_hybrid_aggregator_build_tprol procedure, pass(ag) :: bld_tprol => mld_d_hybrid_aggregator_build_tprol
!!$ procedure, pass(ag) :: mat_asb => mld_d_base_aggregator_mat_asb
!!$ procedure, pass(ag) :: update_level => mld_d_base_aggregator_update_level
!!$ procedure, pass(ag) :: clone => mld_d_base_aggregator_clone
!!$ procedure, pass(ag) :: free => mld_d_base_aggregator_free
!!$ procedure, pass(ag) :: default => mld_d_base_aggregator_default
procedure, nopass :: fmt => mld_d_hybrid_aggregator_fmt procedure, nopass :: fmt => mld_d_hybrid_aggregator_fmt
end type mld_d_hybrid_aggregator_type end type mld_d_hybrid_aggregator_type

@ -94,7 +94,7 @@ module mld_d_symdec_aggregator_mod
type, extends(mld_d_dec_aggregator_type) :: mld_d_symdec_aggregator_type type, extends(mld_d_dec_aggregator_type) :: mld_d_symdec_aggregator_type
contains contains
procedure, pass(ag) :: tprol => mld_d_symdec_aggregator_build_tprol procedure, pass(ag) :: bld_tprol => mld_d_symdec_aggregator_build_tprol
procedure, nopass :: fmt => mld_d_symdec_aggregator_fmt procedure, nopass :: fmt => mld_d_symdec_aggregator_fmt
end type mld_d_symdec_aggregator_type end type mld_d_symdec_aggregator_type

@ -92,7 +92,7 @@ module mld_s_dec_aggregator_mod
type, extends(mld_s_base_aggregator_type) :: mld_s_dec_aggregator_type type, extends(mld_s_base_aggregator_type) :: mld_s_dec_aggregator_type
contains contains
procedure, pass(ag) :: tprol => mld_s_dec_aggregator_build_tprol procedure, pass(ag) :: bld_tprol => mld_s_dec_aggregator_build_tprol
procedure, pass(ag) :: mat_asb => mld_s_dec_aggregator_mat_asb procedure, pass(ag) :: mat_asb => mld_s_dec_aggregator_mat_asb
procedure, nopass :: fmt => mld_s_dec_aggregator_fmt procedure, nopass :: fmt => mld_s_dec_aggregator_fmt
end type mld_s_dec_aggregator_type end type mld_s_dec_aggregator_type

@ -47,7 +47,7 @@
! !
module mld_s_hybrid_aggregator_mod module mld_s_hybrid_aggregator_mod
use mld_s_base_aggregator_mod use mld_s_dec_aggregator_mod
! !
! sm - class(mld_T_base_smoother_type), allocatable ! sm - class(mld_T_base_smoother_type), allocatable
! The current level preconditioner (aka smoother). ! The current level preconditioner (aka smoother).
@ -88,15 +88,10 @@ module mld_s_hybrid_aggregator_mod
! get_nzeros - Number of nonzeros ! get_nzeros - Number of nonzeros
! !
! !
type, extends(mld_s_base_aggregator_type) :: mld_s_hybrid_aggregator_type type, extends(mld_s_dec_aggregator_type) :: mld_s_hybrid_aggregator_type
contains contains
procedure, pass(ag) :: bld_tprol => mld_s_hybrid_aggregator_build_tprol procedure, pass(ag) :: bld_tprol => mld_s_hybrid_aggregator_build_tprol
!!$ procedure, pass(ag) :: mat_asb => mld_s_base_aggregator_mat_asb
!!$ procedure, pass(ag) :: update_level => mld_s_base_aggregator_update_level
!!$ procedure, pass(ag) :: clone => mld_s_base_aggregator_clone
!!$ procedure, pass(ag) :: free => mld_s_base_aggregator_free
!!$ procedure, pass(ag) :: default => mld_s_base_aggregator_default
procedure, nopass :: fmt => mld_s_hybrid_aggregator_fmt procedure, nopass :: fmt => mld_s_hybrid_aggregator_fmt
end type mld_s_hybrid_aggregator_type end type mld_s_hybrid_aggregator_type

@ -94,7 +94,7 @@ module mld_s_symdec_aggregator_mod
type, extends(mld_s_dec_aggregator_type) :: mld_s_symdec_aggregator_type type, extends(mld_s_dec_aggregator_type) :: mld_s_symdec_aggregator_type
contains contains
procedure, pass(ag) :: tprol => mld_s_symdec_aggregator_build_tprol procedure, pass(ag) :: bld_tprol => mld_s_symdec_aggregator_build_tprol
procedure, nopass :: fmt => mld_s_symdec_aggregator_fmt procedure, nopass :: fmt => mld_s_symdec_aggregator_fmt
end type mld_s_symdec_aggregator_type end type mld_s_symdec_aggregator_type

@ -92,7 +92,7 @@ module mld_z_dec_aggregator_mod
type, extends(mld_z_base_aggregator_type) :: mld_z_dec_aggregator_type type, extends(mld_z_base_aggregator_type) :: mld_z_dec_aggregator_type
contains contains
procedure, pass(ag) :: tprol => mld_z_dec_aggregator_build_tprol procedure, pass(ag) :: bld_tprol => mld_z_dec_aggregator_build_tprol
procedure, pass(ag) :: mat_asb => mld_z_dec_aggregator_mat_asb procedure, pass(ag) :: mat_asb => mld_z_dec_aggregator_mat_asb
procedure, nopass :: fmt => mld_z_dec_aggregator_fmt procedure, nopass :: fmt => mld_z_dec_aggregator_fmt
end type mld_z_dec_aggregator_type end type mld_z_dec_aggregator_type

@ -47,7 +47,7 @@
! !
module mld_z_hybrid_aggregator_mod module mld_z_hybrid_aggregator_mod
use mld_z_base_aggregator_mod use mld_z_dec_aggregator_mod
! !
! sm - class(mld_T_base_smoother_type), allocatable ! sm - class(mld_T_base_smoother_type), allocatable
! The current level preconditioner (aka smoother). ! The current level preconditioner (aka smoother).
@ -88,15 +88,10 @@ module mld_z_hybrid_aggregator_mod
! get_nzeros - Number of nonzeros ! get_nzeros - Number of nonzeros
! !
! !
type, extends(mld_z_base_aggregator_type) :: mld_z_hybrid_aggregator_type type, extends(mld_z_dec_aggregator_type) :: mld_z_hybrid_aggregator_type
contains contains
procedure, pass(ag) :: bld_tprol => mld_z_hybrid_aggregator_build_tprol procedure, pass(ag) :: bld_tprol => mld_z_hybrid_aggregator_build_tprol
!!$ procedure, pass(ag) :: mat_asb => mld_z_base_aggregator_mat_asb
!!$ procedure, pass(ag) :: update_level => mld_z_base_aggregator_update_level
!!$ procedure, pass(ag) :: clone => mld_z_base_aggregator_clone
!!$ procedure, pass(ag) :: free => mld_z_base_aggregator_free
!!$ procedure, pass(ag) :: default => mld_z_base_aggregator_default
procedure, nopass :: fmt => mld_z_hybrid_aggregator_fmt procedure, nopass :: fmt => mld_z_hybrid_aggregator_fmt
end type mld_z_hybrid_aggregator_type end type mld_z_hybrid_aggregator_type

@ -94,7 +94,7 @@ module mld_z_symdec_aggregator_mod
type, extends(mld_z_dec_aggregator_type) :: mld_z_symdec_aggregator_type type, extends(mld_z_dec_aggregator_type) :: mld_z_symdec_aggregator_type
contains contains
procedure, pass(ag) :: tprol => mld_z_symdec_aggregator_build_tprol procedure, pass(ag) :: bld_tprol => mld_z_symdec_aggregator_build_tprol
procedure, nopass :: fmt => mld_z_symdec_aggregator_fmt procedure, nopass :: fmt => mld_z_symdec_aggregator_fmt
end type mld_z_symdec_aggregator_type end type mld_z_symdec_aggregator_type

Loading…
Cancel
Save