|
|
|
@ -113,17 +113,20 @@ module mld_d_bcmatch_aggregator_mod
|
|
|
|
|
type, extends(mld_d_base_aggregator_type) :: mld_d_bcmatch_aggregator_type
|
|
|
|
|
integer(psb_ipk_) :: matching_alg
|
|
|
|
|
integer(psb_ipk_) :: n_sweeps
|
|
|
|
|
real(psb_dpk_), allocatable :: w_tmp(:)
|
|
|
|
|
type(bcm_Vector) :: w_par
|
|
|
|
|
real(psb_dpk_), allocatable :: w_tmp(:), w_nxt(:)
|
|
|
|
|
type(bcm_Vector) :: w_par
|
|
|
|
|
integer(psb_ipk_) :: max_csize
|
|
|
|
|
integer(psb_ipk_) :: max_nlevels
|
|
|
|
|
!type(psb_d_vect_type) :: w
|
|
|
|
|
contains
|
|
|
|
|
procedure, pass(ag) :: bld_tprol => mld_d_bcmatch_aggregator_build_tprol
|
|
|
|
|
procedure, pass(ag) :: set => d_bcmatch_aggr_cseti
|
|
|
|
|
procedure, pass(ag) :: cseti => d_bcmatch_aggr_cseti
|
|
|
|
|
procedure, pass(ag) :: default => d_bcmatch_aggr_set_default
|
|
|
|
|
procedure, pass(ag) :: mat_asb => mld_d_bcmatch_aggregator_mat_asb
|
|
|
|
|
procedure, pass(ag) :: update_level => d_bcmatch_aggregator_update_level
|
|
|
|
|
procedure, pass(ag) :: update_next => d_bcmatch_aggregator_update_next
|
|
|
|
|
procedure, pass(ag) :: bld_wnxt => d_bcmatch_bld_wnxt
|
|
|
|
|
procedure, pass(ag) :: bld_default_w => d_bld_default_w
|
|
|
|
|
procedure, pass(ag) :: set_c_default_w => d_set_default_bcm_w
|
|
|
|
|
!!$ procedure, pass(ag) :: clone => mld_d_base_aggregator_clone
|
|
|
|
|
!!$ procedure, pass(ag) :: free => mld_d_bcmatch_aggregator_free
|
|
|
|
|
!!$ procedure, pass(ag) :: default => mld_d_base_aggregator_default
|
|
|
|
@ -195,7 +198,60 @@ module mld_d_bcmatch_aggregator_mod
|
|
|
|
|
|
|
|
|
|
contains
|
|
|
|
|
|
|
|
|
|
subroutine d_bld_default_w(ag,nr)
|
|
|
|
|
use psb_realloc_mod
|
|
|
|
|
implicit none
|
|
|
|
|
class(mld_d_bcmatch_aggregator_type), target, intent(inout) :: ag
|
|
|
|
|
integer(psb_ipk_), intent(in) :: nr
|
|
|
|
|
integer(psb_ipk_) :: info
|
|
|
|
|
call psb_realloc(nr,ag%w_tmp,info)
|
|
|
|
|
if (info /= psb_success_) return
|
|
|
|
|
ag%w_tmp = done
|
|
|
|
|
call ag%set_c_default_w()
|
|
|
|
|
end subroutine d_bld_default_w
|
|
|
|
|
|
|
|
|
|
subroutine d_set_default_bcm_w(ag)
|
|
|
|
|
use psb_realloc_mod
|
|
|
|
|
use iso_c_binding
|
|
|
|
|
implicit none
|
|
|
|
|
class(mld_d_bcmatch_aggregator_type), target, intent(inout) :: ag
|
|
|
|
|
|
|
|
|
|
ag%w_par%size = psb_size(ag%w_tmp)
|
|
|
|
|
ag%w_par%owns_data = 0
|
|
|
|
|
if (ag%w_par%size > 0) call set_cloc(ag%w_tmp, ag%w_par)
|
|
|
|
|
|
|
|
|
|
end subroutine d_set_default_bcm_w
|
|
|
|
|
|
|
|
|
|
subroutine set_cloc(vect,w_par)
|
|
|
|
|
use iso_c_binding
|
|
|
|
|
real(psb_dpk_), target :: vect(:)
|
|
|
|
|
type(bcm_Vector) :: w_par
|
|
|
|
|
|
|
|
|
|
w_par%data = c_loc(vect)
|
|
|
|
|
end subroutine set_cloc
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine d_bcmatch_bld_wnxt(ag,ilaggr,valaggr,nx)
|
|
|
|
|
use psb_realloc_mod
|
|
|
|
|
implicit none
|
|
|
|
|
class(mld_d_bcmatch_aggregator_type), target, intent(inout) :: ag
|
|
|
|
|
integer(psb_ipk_), intent(in) :: ilaggr(:)
|
|
|
|
|
real(psb_dpk_), intent(in) :: valaggr(:)
|
|
|
|
|
integer(psb_ipk_), intent(in) :: nx
|
|
|
|
|
|
|
|
|
|
integer(psb_ipk_) :: info,i,j
|
|
|
|
|
|
|
|
|
|
call psb_realloc(nx,ag%w_nxt,info)
|
|
|
|
|
associate(w_nxt => ag%w_nxt, w_tmp=>ag%w_tmp)
|
|
|
|
|
w_nxt = dzero
|
|
|
|
|
do j=1, size(ilaggr)
|
|
|
|
|
i = ilaggr(j)
|
|
|
|
|
w_nxt(i) = w_nxt(i) + valaggr(j)*w_tmp(j)
|
|
|
|
|
end do
|
|
|
|
|
end associate
|
|
|
|
|
|
|
|
|
|
end subroutine d_bcmatch_bld_wnxt
|
|
|
|
|
|
|
|
|
|
function mld_d_bcmatch_aggregator_fmt() result(val)
|
|
|
|
|
implicit none
|
|
|
|
|
character(len=32) :: val
|
|
|
|
@ -203,7 +259,8 @@ contains
|
|
|
|
|
val = "BootCMatch aggregation"
|
|
|
|
|
end function mld_d_bcmatch_aggregator_fmt
|
|
|
|
|
|
|
|
|
|
subroutine d_bcmatch_aggregator_update_level(ag,agnext,info)
|
|
|
|
|
subroutine d_bcmatch_aggregator_update_next(ag,agnext,info)
|
|
|
|
|
use psb_realloc_mod
|
|
|
|
|
implicit none
|
|
|
|
|
class(mld_d_bcmatch_aggregator_type), target, intent(inout) :: ag
|
|
|
|
|
class(mld_d_base_aggregator_type), target, intent(inout) :: agnext
|
|
|
|
@ -212,17 +269,20 @@ contains
|
|
|
|
|
!
|
|
|
|
|
!
|
|
|
|
|
select type(agnext)
|
|
|
|
|
type is (mld_d_bcmatch_aggregator_type)
|
|
|
|
|
class is (mld_d_bcmatch_aggregator_type)
|
|
|
|
|
agnext%matching_alg = ag%matching_alg
|
|
|
|
|
agnext%n_sweeps = ag%n_sweeps
|
|
|
|
|
agnext%max_csize = ag%max_csize
|
|
|
|
|
agnext%max_nlevels = ag%max_nlevels
|
|
|
|
|
! Is this going to generate shallow copies/memory leaks/double frees?
|
|
|
|
|
! To be investigated further.
|
|
|
|
|
agnext%w_par = ag%w_par
|
|
|
|
|
call psb_safe_ab_cpy(ag%w_nxt,agnext%w_tmp,info)
|
|
|
|
|
call agnext%set_c_default_w()
|
|
|
|
|
class default
|
|
|
|
|
! What should we do here?
|
|
|
|
|
end select
|
|
|
|
|
info = 0
|
|
|
|
|
end subroutine d_bcmatch_aggregator_update_level
|
|
|
|
|
end subroutine d_bcmatch_aggregator_update_next
|
|
|
|
|
|
|
|
|
|
subroutine d_bcmatch_aggr_cseti(ag,what,val,info)
|
|
|
|
|
|
|
|
|
@ -238,31 +298,22 @@ contains
|
|
|
|
|
info = psb_success_
|
|
|
|
|
|
|
|
|
|
select case(what)
|
|
|
|
|
case('BCM_MATCH_ALG')
|
|
|
|
|
ag%matching_alg=val
|
|
|
|
|
case('BCM_SWEEPS')
|
|
|
|
|
ag%n_sweeps=val
|
|
|
|
|
case('BCM_MAX_CSIZE')
|
|
|
|
|
ag%max_csize=val
|
|
|
|
|
case('BCM_MAX_NLEVELS')
|
|
|
|
|
ag%max_nlevels=val
|
|
|
|
|
case('BCM_W_SIZE')
|
|
|
|
|
ag%w_par%size=val
|
|
|
|
|
ag%w_par%owns_data=0
|
|
|
|
|
allocate(ag%w_tmp(val))
|
|
|
|
|
ag%w_tmp = 1.0_psb_dpk_
|
|
|
|
|
call set_cloc(ag%w_tmp, ag%w_par)
|
|
|
|
|
case default
|
|
|
|
|
case('BCM_MATCH_ALG')
|
|
|
|
|
ag%matching_alg=val
|
|
|
|
|
case('BCM_SWEEPS')
|
|
|
|
|
ag%n_sweeps=val
|
|
|
|
|
case('BCM_MAX_CSIZE')
|
|
|
|
|
ag%max_csize=val
|
|
|
|
|
case('BCM_MAX_NLEVELS')
|
|
|
|
|
ag%max_nlevels=val
|
|
|
|
|
case('BCM_W_SIZE')
|
|
|
|
|
!write(0,*) 'Setting W_SIZE'
|
|
|
|
|
call ag%bld_default_w(val)
|
|
|
|
|
|
|
|
|
|
case default
|
|
|
|
|
|
|
|
|
|
end select
|
|
|
|
|
return
|
|
|
|
|
contains
|
|
|
|
|
subroutine set_cloc(vect,w_par)
|
|
|
|
|
real(psb_dpk_), target :: vect(:)
|
|
|
|
|
type(bcm_Vector) :: w_par
|
|
|
|
|
|
|
|
|
|
w_par%data = c_loc(vect)
|
|
|
|
|
end subroutine set_cloc
|
|
|
|
|
|
|
|
|
|
end subroutine d_bcmatch_aggr_cseti
|
|
|
|
|
|
|
|
|
|
subroutine d_bcmatch_aggr_set_default(ag)
|
|
|
|
@ -272,10 +323,10 @@ contains
|
|
|
|
|
! Arguments
|
|
|
|
|
class(mld_d_bcmatch_aggregator_type), intent(inout) :: ag
|
|
|
|
|
character(len=20) :: name='d_bcmatch_aggr_set_default'
|
|
|
|
|
ag%matching_alg=0
|
|
|
|
|
ag%n_sweeps=1
|
|
|
|
|
ag%max_nlevels=36
|
|
|
|
|
ag%max_csize=10
|
|
|
|
|
ag%matching_alg = 0
|
|
|
|
|
ag%n_sweeps = 1
|
|
|
|
|
ag%max_nlevels = 36
|
|
|
|
|
ag%max_csize = 10
|
|
|
|
|
|
|
|
|
|
return
|
|
|
|
|
|
|
|
|
|