Take out spurious csize and maxnlev from parmatch aggregator object.

fix-sludist7
Salvatore Filippone 3 years ago
parent 794080e386
commit a8f4009cb1

@ -132,8 +132,6 @@ module amg_d_parmatch_aggregator_mod
type(psb_dspmat_type), allocatable :: prol, restr type(psb_dspmat_type), allocatable :: prol, restr
type(psb_dspmat_type), allocatable :: ac, base_a, rwa type(psb_dspmat_type), allocatable :: ac, base_a, rwa
type(psb_desc_type), allocatable :: desc_ac, desc_ax, base_desc, rwdesc type(psb_desc_type), allocatable :: desc_ac, desc_ax, base_desc, rwdesc
integer(psb_ipk_) :: max_csize
integer(psb_ipk_) :: max_nlevels
logical :: reproducible_matching = .false. logical :: reproducible_matching = .false.
logical :: need_symmetrize = .false. logical :: need_symmetrize = .false.
logical :: unsmoothed_hierarchy = .true. logical :: unsmoothed_hierarchy = .true.
@ -452,10 +450,10 @@ contains
& agnext%matching_alg = ag%matching_alg & agnext%matching_alg = ag%matching_alg
if (.not.is_legal_nsweeps(agnext%n_sweeps))& if (.not.is_legal_nsweeps(agnext%n_sweeps))&
& agnext%n_sweeps = ag%n_sweeps & agnext%n_sweeps = ag%n_sweeps
if (.not.is_legal_csize(agnext%max_csize))& !!$ if (.not.is_legal_csize(agnext%max_csize))&
& agnext%max_csize = ag%max_csize !!$ & agnext%max_csize = ag%max_csize
if (.not.is_legal_nlevels(agnext%max_nlevels))& !!$ if (.not.is_legal_nlevels(agnext%max_nlevels))&
& agnext%max_nlevels = ag%max_nlevels !!$ & agnext%max_nlevels = ag%max_nlevels
! Is this going to generate shallow copies/memory leaks/double frees? ! Is this going to generate shallow copies/memory leaks/double frees?
! To be investigated further. ! To be investigated further.
call psb_safe_ab_cpy(ag%w_nxt,agnext%w,info) call psb_safe_ab_cpy(ag%w_nxt,agnext%w,info)
@ -540,10 +538,6 @@ contains
case('AGGR_SIZE') case('AGGR_SIZE')
ag%orig_aggr_size = val ag%orig_aggr_size = val
ag%n_sweeps=max(1,ceiling(log(val*1.0)/log(2.0))) ag%n_sweeps=max(1,ceiling(log(val*1.0)/log(2.0)))
case('PRMC_MAX_CSIZE')
ag%max_csize=val
case('PRMC_MAX_NLEVELS')
ag%max_nlevels=val
case('PRMC_W_SIZE') case('PRMC_W_SIZE')
call ag%bld_default_w(val) call ag%bld_default_w(val)
case('PRMC_REPRODUCIBLE_MATCHING') case('PRMC_REPRODUCIBLE_MATCHING')
@ -569,8 +563,8 @@ contains
ag%matching_alg = 0 ag%matching_alg = 0
ag%n_sweeps = 1 ag%n_sweeps = 1
ag%jacobi_sweeps = 0 ag%jacobi_sweeps = 0
ag%max_nlevels = 36 !!$ ag%max_nlevels = 36
ag%max_csize = -1 !!$ ag%max_csize = -1
! !
! Apparently BootCMatch works better ! Apparently BootCMatch works better
! by keeping all entries ! by keeping all entries

@ -132,8 +132,6 @@ module amg_s_parmatch_aggregator_mod
type(psb_sspmat_type), allocatable :: prol, restr type(psb_sspmat_type), allocatable :: prol, restr
type(psb_sspmat_type), allocatable :: ac, base_a, rwa type(psb_sspmat_type), allocatable :: ac, base_a, rwa
type(psb_desc_type), allocatable :: desc_ac, desc_ax, base_desc, rwdesc type(psb_desc_type), allocatable :: desc_ac, desc_ax, base_desc, rwdesc
integer(psb_ipk_) :: max_csize
integer(psb_ipk_) :: max_nlevels
logical :: reproducible_matching = .false. logical :: reproducible_matching = .false.
logical :: need_symmetrize = .false. logical :: need_symmetrize = .false.
logical :: unsmoothed_hierarchy = .true. logical :: unsmoothed_hierarchy = .true.
@ -452,10 +450,10 @@ contains
& agnext%matching_alg = ag%matching_alg & agnext%matching_alg = ag%matching_alg
if (.not.is_legal_nsweeps(agnext%n_sweeps))& if (.not.is_legal_nsweeps(agnext%n_sweeps))&
& agnext%n_sweeps = ag%n_sweeps & agnext%n_sweeps = ag%n_sweeps
if (.not.is_legal_csize(agnext%max_csize))& !!$ if (.not.is_legal_csize(agnext%max_csize))&
& agnext%max_csize = ag%max_csize !!$ & agnext%max_csize = ag%max_csize
if (.not.is_legal_nlevels(agnext%max_nlevels))& !!$ if (.not.is_legal_nlevels(agnext%max_nlevels))&
& agnext%max_nlevels = ag%max_nlevels !!$ & agnext%max_nlevels = ag%max_nlevels
! Is this going to generate shallow copies/memory leaks/double frees? ! Is this going to generate shallow copies/memory leaks/double frees?
! To be investigated further. ! To be investigated further.
call psb_safe_ab_cpy(ag%w_nxt,agnext%w,info) call psb_safe_ab_cpy(ag%w_nxt,agnext%w,info)
@ -540,10 +538,6 @@ contains
case('AGGR_SIZE') case('AGGR_SIZE')
ag%orig_aggr_size = val ag%orig_aggr_size = val
ag%n_sweeps=max(1,ceiling(log(val*1.0)/log(2.0))) ag%n_sweeps=max(1,ceiling(log(val*1.0)/log(2.0)))
case('PRMC_MAX_CSIZE')
ag%max_csize=val
case('PRMC_MAX_NLEVELS')
ag%max_nlevels=val
case('PRMC_W_SIZE') case('PRMC_W_SIZE')
call ag%bld_default_w(val) call ag%bld_default_w(val)
case('PRMC_REPRODUCIBLE_MATCHING') case('PRMC_REPRODUCIBLE_MATCHING')
@ -569,8 +563,8 @@ contains
ag%matching_alg = 0 ag%matching_alg = 0
ag%n_sweeps = 1 ag%n_sweeps = 1
ag%jacobi_sweeps = 0 ag%jacobi_sweeps = 0
ag%max_nlevels = 36 !!$ ag%max_nlevels = 36
ag%max_csize = -1 !!$ ag%max_csize = -1
! !
! Apparently BootCMatch works better ! Apparently BootCMatch works better
! by keeping all entries ! by keeping all entries

@ -68,7 +68,8 @@ subroutine amg_d_parmatch_aggregator_build_tprol(ag,parms,ag_data,&
real(psb_dpk_), allocatable :: tmpw(:), tmpwnxt(:) real(psb_dpk_), allocatable :: tmpw(:), tmpwnxt(:)
integer(psb_lpk_), allocatable :: ixaggr(:), nxaggr(:), tlaggr(:), ivr(:) integer(psb_lpk_), allocatable :: ixaggr(:), nxaggr(:), tlaggr(:), ivr(:)
type(psb_dspmat_type) :: a_tmp type(psb_dspmat_type) :: a_tmp
integer(c_int) :: match_algorithm, n_sweeps, target_csize, max_nlevels integer(psb_ipk_) :: match_algorithm, n_sweeps
integer(psb_lpk_) :: target_csize
character(len=40) :: name, ch_err character(len=40) :: name, ch_err
character(len=80) :: fname, prefix_ character(len=80) :: fname, prefix_
type(psb_ctxt_type) :: ictxt type(psb_ctxt_type) :: ictxt
@ -133,11 +134,6 @@ subroutine amg_d_parmatch_aggregator_build_tprol(ag,parms,ag_data,&
else else
target_csize = ag_data%min_coarse_size target_csize = ag_data%min_coarse_size
end if end if
if (ag%max_nlevels > 0) then
max_nlevels = ag%max_nlevels
else
max_nlevels = ag_data%max_levs
end if
if (.true.) then if (.true.) then
block block
integer(psb_ipk_) :: ipv(2) integer(psb_ipk_) :: ipv(2)

@ -68,7 +68,8 @@ subroutine amg_s_parmatch_aggregator_build_tprol(ag,parms,ag_data,&
real(psb_spk_), allocatable :: tmpw(:), tmpwnxt(:) real(psb_spk_), allocatable :: tmpw(:), tmpwnxt(:)
integer(psb_lpk_), allocatable :: ixaggr(:), nxaggr(:), tlaggr(:), ivr(:) integer(psb_lpk_), allocatable :: ixaggr(:), nxaggr(:), tlaggr(:), ivr(:)
type(psb_sspmat_type) :: a_tmp type(psb_sspmat_type) :: a_tmp
integer(c_int) :: match_algorithm, n_sweeps, target_csize, max_nlevels integer(psb_ipk_) :: match_algorithm, n_sweeps
integer(psb_lpk_) :: target_csize
character(len=40) :: name, ch_err character(len=40) :: name, ch_err
character(len=80) :: fname, prefix_ character(len=80) :: fname, prefix_
type(psb_ctxt_type) :: ictxt type(psb_ctxt_type) :: ictxt
@ -133,11 +134,6 @@ subroutine amg_s_parmatch_aggregator_build_tprol(ag,parms,ag_data,&
else else
target_csize = ag_data%min_coarse_size target_csize = ag_data%min_coarse_size
end if end if
if (ag%max_nlevels > 0) then
max_nlevels = ag%max_nlevels
else
max_nlevels = ag_data%max_levs
end if
if (.true.) then if (.true.) then
block block
integer(psb_ipk_) :: ipv(2) integer(psb_ipk_) :: ipv(2)

Loading…
Cancel
Save