Renamed VMB and HYB into SOC1 and SOC2.

stopcriterion
Salvatore Filippone 7 years ago
parent 7732bb90d3
commit d6e990b04c

@ -12,25 +12,25 @@ OBJS= \
mld_s_dec_aggregator_mat_asb.o \ mld_s_dec_aggregator_mat_asb.o \
mld_s_dec_aggregator_tprol.o \ mld_s_dec_aggregator_tprol.o \
mld_s_symdec_aggregator_tprol.o \ mld_s_symdec_aggregator_tprol.o \
mld_s_map_to_tprol.o mld_s_vmb_map_bld.o mld_s_hyb_map_bld.o\ mld_s_map_to_tprol.o mld_s_soc1_map_bld.o mld_s_soc2_map_bld.o\
mld_saggrmat_biz_asb.o mld_saggrmat_minnrg_asb.o\ mld_saggrmat_biz_asb.o mld_saggrmat_minnrg_asb.o\
mld_saggrmat_nosmth_asb.o mld_saggrmat_smth_asb.o \ mld_saggrmat_nosmth_asb.o mld_saggrmat_smth_asb.o \
mld_d_dec_aggregator_mat_asb.o \ mld_d_dec_aggregator_mat_asb.o \
mld_d_dec_aggregator_tprol.o \ mld_d_dec_aggregator_tprol.o \
mld_d_symdec_aggregator_tprol.o \ mld_d_symdec_aggregator_tprol.o \
mld_d_map_to_tprol.o mld_d_vmb_map_bld.o mld_d_hyb_map_bld.o\ mld_d_map_to_tprol.o mld_d_soc1_map_bld.o mld_d_soc2_map_bld.o\
mld_daggrmat_biz_asb.o mld_daggrmat_minnrg_asb.o\ mld_daggrmat_biz_asb.o mld_daggrmat_minnrg_asb.o\
mld_daggrmat_nosmth_asb.o mld_daggrmat_smth_asb.o \ mld_daggrmat_nosmth_asb.o mld_daggrmat_smth_asb.o \
mld_c_dec_aggregator_mat_asb.o \ mld_c_dec_aggregator_mat_asb.o \
mld_c_dec_aggregator_tprol.o \ mld_c_dec_aggregator_tprol.o \
mld_c_symdec_aggregator_tprol.o \ mld_c_symdec_aggregator_tprol.o \
mld_c_map_to_tprol.o mld_c_vmb_map_bld.o mld_c_hyb_map_bld.o\ mld_c_map_to_tprol.o mld_c_soc1_map_bld.o mld_c_soc2_map_bld.o\
mld_caggrmat_biz_asb.o mld_caggrmat_minnrg_asb.o\ mld_caggrmat_biz_asb.o mld_caggrmat_minnrg_asb.o\
mld_caggrmat_nosmth_asb.o mld_caggrmat_smth_asb.o \ mld_caggrmat_nosmth_asb.o mld_caggrmat_smth_asb.o \
mld_z_dec_aggregator_mat_asb.o \ mld_z_dec_aggregator_mat_asb.o \
mld_z_dec_aggregator_tprol.o \ mld_z_dec_aggregator_tprol.o \
mld_z_symdec_aggregator_tprol.o \ mld_z_symdec_aggregator_tprol.o \
mld_z_map_to_tprol.o mld_z_vmb_map_bld.o mld_z_hyb_map_bld.o\ mld_z_map_to_tprol.o mld_z_soc1_map_bld.o mld_z_soc2_map_bld.o\
mld_zaggrmat_biz_asb.o mld_zaggrmat_minnrg_asb.o\ mld_zaggrmat_biz_asb.o mld_zaggrmat_minnrg_asb.o\
mld_zaggrmat_nosmth_asb.o mld_zaggrmat_smth_asb.o mld_zaggrmat_nosmth_asb.o mld_zaggrmat_smth_asb.o

@ -40,7 +40,7 @@
! Subroutine: mld_c_dec_aggregator_tprol ! Subroutine: mld_c_dec_aggregator_tprol
! Version: complex ! Version: complex
! !
! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! This routine is mainly an interface to map_bld where the real work is performed.
! It takes care of some consistency checking, and calls map_to_tprol, which is ! It takes care of some consistency checking, and calls map_to_tprol, which is
! refactored and shared among all the aggregation methods that produce a simple ! refactored and shared among all the aggregation methods that produce a simple
! integer mapping. ! integer mapping.
@ -111,12 +111,11 @@ subroutine mld_c_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_
call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info)
!!$ call mld_c_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info)
if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
if (info /= psb_success_) then if (info /= psb_success_) then
info=psb_err_from_subroutine_ info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') call psb_errpush(info,name,a_err='map_bld/map_to_tprol')
goto 9999 goto 9999
endif endif

@ -1,130 +0,0 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
! File: mld_c_hybrid_aggregator_tprol.f90
!
! Subroutine: mld_c_hybrid_aggregator_tprol
! Version: complex
!
!
! This routine is mainly an interface to hyb_map_bld where the real work is performed.
! It takes care of some consistency checking, and calls map_to_tprol, which is
! refactored and shared among all the aggregation methods that produce a simple
! integer mapping.
!
!
! Arguments:
! p - type(mld_c_onelev_type), input/output.
! The 'one-level' data structure containing the control
! parameters and (eventually) coarse matrix and prolongator/restrictors.
!
! a - type(psb_cspmat_type).
! The sparse matrix structure containing the local part of the
! fine-level matrix.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of a.
! ilaggr - integer, dimension(:), allocatable, output
! The mapping between the row indices of the coarse-level
! matrix and the row indices of the fine-level matrix.
! ilaggr(i)=j means that node i in the adjacency graph
! of the fine-level matrix is mapped onto node j in the
! adjacency graph of the coarse-level matrix. Note that on exit the indices
! will be shifted so as to make sure the ranges on the various processes do not
! overlap.
! nlaggr - integer, dimension(:), allocatable, output
! nlaggr(i) contains the aggregates held by process i.
! op_prol - type(psb_cspmat_type), output
! The tentative prolongator, based on ilaggr.
!
! info - integer, output.
! Error code.
!
subroutine mld_c_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
use psb_base_mod
use mld_c_prec_type
use mld_c_hybrid_aggregator_mod, mld_protect_name => mld_c_hybrid_aggregator_build_tprol
use mld_c_inner_mod
implicit none
class(mld_c_hybrid_aggregator_type), target, intent(inout) :: ag
type(mld_sml_parms), intent(inout) :: parms
type(psb_cspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_cspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
character(len=20) :: name
integer(psb_mpik_) :: ictxt, np, me
integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ntaggr
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_c_hybrid_aggregator_tprol'
if (psb_get_errstatus().ne.0) return
call psb_erractionsave(err_act)
debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level()
info = psb_success_
ictxt = desc_a%get_context()
call psb_info(ictxt,me,np)
call mld_check_def(parms%ml_cycle,'Multilevel cycle',&
& mld_mult_ml_,is_legal_ml_cycle)
call mld_check_def(parms%par_aggr_alg,'Aggregation',&
& mld_dec_aggr_,is_legal_ml_par_aggr_alg)
call mld_check_def(parms%aggr_ord,'Ordering',&
& mld_aggr_ord_nat_,is_legal_ml_aggr_ord)
call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs)
call mld_c_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info)
if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
if (info /= psb_success_) then
info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='hyb_map_bld/map_to_tprol')
goto 9999
endif
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_c_hybrid_aggregator_build_tprol

@ -36,9 +36,9 @@
! !
! !
! !
! File: mld_c_vmb_map__bld.f90 ! File: mld_c_soc1_map__bld.f90
! !
! Subroutine: mld_c_vmb_map_bld ! Subroutine: mld_c_soc1_map_bld
! Version: complex ! Version: complex
! !
! This routine builds the tentative prolongator based on the ! This routine builds the tentative prolongator based on the
@ -67,11 +67,11 @@
! !
! !
! !
subroutine mld_c_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) subroutine mld_c_soc1_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
use psb_base_mod use psb_base_mod
use mld_base_prec_type use mld_base_prec_type
use mld_c_inner_mod!, mld_protect_name => mld_c_vmb_map_bld use mld_c_inner_mod!, mld_protect_name => mld_c_soc1_map_bld
implicit none implicit none
@ -98,7 +98,7 @@ subroutine mld_c_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
if (psb_get_errstatus() /= 0) return if (psb_get_errstatus() /= 0) return
info=psb_success_ info=psb_success_
name = 'mld_vmb_map_bld' name = 'mld_soc1_map_bld'
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
debug_unit = psb_get_debug_unit() debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level() debug_level = psb_get_debug_level()
@ -318,5 +318,5 @@ subroutine mld_c_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
return return
end subroutine mld_c_vmb_map_bld end subroutine mld_c_soc1_map_bld

@ -36,13 +36,13 @@
! !
! !
! !
! File: mld_c_hyb_map__bld.f90 ! File: mld_c_soc2_map__bld.f90
! !
! Subroutine: mld_c_hyb_map_bld ! Subroutine: mld_c_soc2_map_bld
! Version: complex ! Version: complex
! !
! The aggregator object hosts the aggregation method for building ! The aggregator object hosts the aggregation method for building
! the multilevel hierarchy. This variant is based on the hybrid method ! the multilevel hierarchy. This variant is based on the method
! presented in ! presented in
! !
! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: ! S. Gratton, P. Henon, P. Jiranek and X. Vasseur:
@ -66,11 +66,11 @@
! !
! !
! !
subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) subroutine mld_c_soc2_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
use psb_base_mod use psb_base_mod
use mld_base_prec_type use mld_base_prec_type
use mld_c_inner_mod!, mld_protect_name => mld_c_hyb_map_bld use mld_c_inner_mod!, mld_protect_name => mld_c_soc2_map_bld
implicit none implicit none
@ -98,7 +98,7 @@ subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
if (psb_get_errstatus() /= 0) return if (psb_get_errstatus() /= 0) return
info=psb_success_ info=psb_success_
name = 'mld_hyb_map_bld' name = 'mld_soc2_map_bld'
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
debug_unit = psb_get_debug_unit() debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level() debug_level = psb_get_debug_level()
@ -326,5 +326,5 @@ subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
return return
end subroutine mld_c_hyb_map_bld end subroutine mld_c_soc2_map_bld

@ -41,7 +41,7 @@
! Version: complex ! Version: complex
! !
! !
! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! This routine is mainly an interface to map_bld where the real work is performed.
! It takes care of some consistency checking, and calls map_to_tprol, which is ! It takes care of some consistency checking, and calls map_to_tprol, which is
! refactored and shared among all the aggregation methods that produce a simple ! refactored and shared among all the aggregation methods that produce a simple
! integer mapping. ! integer mapping.
@ -127,13 +127,13 @@ subroutine mld_c_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,
if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) call atmp%cscnv(info,type='CSR')
if (info == psb_success_) & if (info == psb_success_) &
& call mld_c_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) & call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info)
if (info == psb_success_) call atmp%free() if (info == psb_success_) call atmp%free()
if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
if (info /= psb_success_) then if (info /= psb_success_) then
info=psb_err_from_subroutine_ info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') call psb_errpush(info,name,a_err='map_bld/map_to_tprol')
goto 9999 goto 9999
endif endif

@ -40,7 +40,7 @@
! Subroutine: mld_d_dec_aggregator_tprol ! Subroutine: mld_d_dec_aggregator_tprol
! Version: real ! Version: real
! !
! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! This routine is mainly an interface to map_bld where the real work is performed.
! It takes care of some consistency checking, and calls map_to_tprol, which is ! It takes care of some consistency checking, and calls map_to_tprol, which is
! refactored and shared among all the aggregation methods that produce a simple ! refactored and shared among all the aggregation methods that produce a simple
! integer mapping. ! integer mapping.
@ -111,12 +111,11 @@ subroutine mld_d_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_
call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info)
!!$ call mld_d_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info)
if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
if (info /= psb_success_) then if (info /= psb_success_) then
info=psb_err_from_subroutine_ info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') call psb_errpush(info,name,a_err='map_bld/map_to_tprol')
goto 9999 goto 9999
endif endif

@ -1,130 +0,0 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
! File: mld_d_hybrid_aggregator_tprol.f90
!
! Subroutine: mld_d_hybrid_aggregator_tprol
! Version: real
!
!
! This routine is mainly an interface to hyb_map_bld where the real work is performed.
! It takes care of some consistency checking, and calls map_to_tprol, which is
! refactored and shared among all the aggregation methods that produce a simple
! integer mapping.
!
!
! Arguments:
! p - type(mld_d_onelev_type), input/output.
! The 'one-level' data structure containing the control
! parameters and (eventually) coarse matrix and prolongator/restrictors.
!
! a - type(psb_dspmat_type).
! The sparse matrix structure containing the local part of the
! fine-level matrix.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of a.
! ilaggr - integer, dimension(:), allocatable, output
! The mapping between the row indices of the coarse-level
! matrix and the row indices of the fine-level matrix.
! ilaggr(i)=j means that node i in the adjacency graph
! of the fine-level matrix is mapped onto node j in the
! adjacency graph of the coarse-level matrix. Note that on exit the indices
! will be shifted so as to make sure the ranges on the various processes do not
! overlap.
! nlaggr - integer, dimension(:), allocatable, output
! nlaggr(i) contains the aggregates held by process i.
! op_prol - type(psb_dspmat_type), output
! The tentative prolongator, based on ilaggr.
!
! info - integer, output.
! Error code.
!
subroutine mld_d_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
use psb_base_mod
use mld_d_prec_type
use mld_d_hybrid_aggregator_mod, mld_protect_name => mld_d_hybrid_aggregator_build_tprol
use mld_d_inner_mod
implicit none
class(mld_d_hybrid_aggregator_type), target, intent(inout) :: ag
type(mld_dml_parms), intent(inout) :: parms
type(psb_dspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_dspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
character(len=20) :: name
integer(psb_mpik_) :: ictxt, np, me
integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ntaggr
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_d_hybrid_aggregator_tprol'
if (psb_get_errstatus().ne.0) return
call psb_erractionsave(err_act)
debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level()
info = psb_success_
ictxt = desc_a%get_context()
call psb_info(ictxt,me,np)
call mld_check_def(parms%ml_cycle,'Multilevel cycle',&
& mld_mult_ml_,is_legal_ml_cycle)
call mld_check_def(parms%par_aggr_alg,'Aggregation',&
& mld_dec_aggr_,is_legal_ml_par_aggr_alg)
call mld_check_def(parms%aggr_ord,'Ordering',&
& mld_aggr_ord_nat_,is_legal_ml_aggr_ord)
call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs)
call mld_d_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info)
if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
if (info /= psb_success_) then
info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='hyb_map_bld/map_to_tprol')
goto 9999
endif
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_d_hybrid_aggregator_build_tprol

@ -36,9 +36,9 @@
! !
! !
! !
! File: mld_d_vmb_map__bld.f90 ! File: mld_d_soc1_map__bld.f90
! !
! Subroutine: mld_d_vmb_map_bld ! Subroutine: mld_d_soc1_map_bld
! Version: real ! Version: real
! !
! This routine builds the tentative prolongator based on the ! This routine builds the tentative prolongator based on the
@ -67,11 +67,11 @@
! !
! !
! !
subroutine mld_d_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) subroutine mld_d_soc1_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
use psb_base_mod use psb_base_mod
use mld_base_prec_type use mld_base_prec_type
use mld_d_inner_mod!, mld_protect_name => mld_d_vmb_map_bld use mld_d_inner_mod!, mld_protect_name => mld_d_soc1_map_bld
implicit none implicit none
@ -98,7 +98,7 @@ subroutine mld_d_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
if (psb_get_errstatus() /= 0) return if (psb_get_errstatus() /= 0) return
info=psb_success_ info=psb_success_
name = 'mld_vmb_map_bld' name = 'mld_soc1_map_bld'
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
debug_unit = psb_get_debug_unit() debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level() debug_level = psb_get_debug_level()
@ -318,5 +318,5 @@ subroutine mld_d_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
return return
end subroutine mld_d_vmb_map_bld end subroutine mld_d_soc1_map_bld

@ -36,13 +36,13 @@
! !
! !
! !
! File: mld_d_hyb_map__bld.f90 ! File: mld_d_soc2_map__bld.f90
! !
! Subroutine: mld_d_hyb_map_bld ! Subroutine: mld_d_soc2_map_bld
! Version: real ! Version: real
! !
! The aggregator object hosts the aggregation method for building ! The aggregator object hosts the aggregation method for building
! the multilevel hierarchy. This variant is based on the hybrid method ! the multilevel hierarchy. This variant is based on the method
! presented in ! presented in
! !
! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: ! S. Gratton, P. Henon, P. Jiranek and X. Vasseur:
@ -66,11 +66,11 @@
! !
! !
! !
subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) subroutine mld_d_soc2_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
use psb_base_mod use psb_base_mod
use mld_base_prec_type use mld_base_prec_type
use mld_d_inner_mod!, mld_protect_name => mld_d_hyb_map_bld use mld_d_inner_mod!, mld_protect_name => mld_d_soc2_map_bld
implicit none implicit none
@ -98,7 +98,7 @@ subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
if (psb_get_errstatus() /= 0) return if (psb_get_errstatus() /= 0) return
info=psb_success_ info=psb_success_
name = 'mld_hyb_map_bld' name = 'mld_soc2_map_bld'
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
debug_unit = psb_get_debug_unit() debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level() debug_level = psb_get_debug_level()
@ -326,5 +326,5 @@ subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
return return
end subroutine mld_d_hyb_map_bld end subroutine mld_d_soc2_map_bld

@ -41,7 +41,7 @@
! Version: real ! Version: real
! !
! !
! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! This routine is mainly an interface to map_bld where the real work is performed.
! It takes care of some consistency checking, and calls map_to_tprol, which is ! It takes care of some consistency checking, and calls map_to_tprol, which is
! refactored and shared among all the aggregation methods that produce a simple ! refactored and shared among all the aggregation methods that produce a simple
! integer mapping. ! integer mapping.
@ -127,13 +127,13 @@ subroutine mld_d_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,
if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) call atmp%cscnv(info,type='CSR')
if (info == psb_success_) & if (info == psb_success_) &
& call mld_d_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) & call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info)
if (info == psb_success_) call atmp%free() if (info == psb_success_) call atmp%free()
if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
if (info /= psb_success_) then if (info /= psb_success_) then
info=psb_err_from_subroutine_ info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') call psb_errpush(info,name,a_err='map_bld/map_to_tprol')
goto 9999 goto 9999
endif endif

@ -40,7 +40,7 @@
! Subroutine: mld_s_dec_aggregator_tprol ! Subroutine: mld_s_dec_aggregator_tprol
! Version: real ! Version: real
! !
! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! This routine is mainly an interface to map_bld where the real work is performed.
! It takes care of some consistency checking, and calls map_to_tprol, which is ! It takes care of some consistency checking, and calls map_to_tprol, which is
! refactored and shared among all the aggregation methods that produce a simple ! refactored and shared among all the aggregation methods that produce a simple
! integer mapping. ! integer mapping.
@ -111,12 +111,11 @@ subroutine mld_s_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_
call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info)
!!$ call mld_s_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info)
if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
if (info /= psb_success_) then if (info /= psb_success_) then
info=psb_err_from_subroutine_ info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') call psb_errpush(info,name,a_err='map_bld/map_to_tprol')
goto 9999 goto 9999
endif endif

@ -1,130 +0,0 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
! File: mld_s_hybrid_aggregator_tprol.f90
!
! Subroutine: mld_s_hybrid_aggregator_tprol
! Version: real
!
!
! This routine is mainly an interface to hyb_map_bld where the real work is performed.
! It takes care of some consistency checking, and calls map_to_tprol, which is
! refactored and shared among all the aggregation methods that produce a simple
! integer mapping.
!
!
! Arguments:
! p - type(mld_s_onelev_type), input/output.
! The 'one-level' data structure containing the control
! parameters and (eventually) coarse matrix and prolongator/restrictors.
!
! a - type(psb_sspmat_type).
! The sparse matrix structure containing the local part of the
! fine-level matrix.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of a.
! ilaggr - integer, dimension(:), allocatable, output
! The mapping between the row indices of the coarse-level
! matrix and the row indices of the fine-level matrix.
! ilaggr(i)=j means that node i in the adjacency graph
! of the fine-level matrix is mapped onto node j in the
! adjacency graph of the coarse-level matrix. Note that on exit the indices
! will be shifted so as to make sure the ranges on the various processes do not
! overlap.
! nlaggr - integer, dimension(:), allocatable, output
! nlaggr(i) contains the aggregates held by process i.
! op_prol - type(psb_sspmat_type), output
! The tentative prolongator, based on ilaggr.
!
! info - integer, output.
! Error code.
!
subroutine mld_s_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
use psb_base_mod
use mld_s_prec_type
use mld_s_hybrid_aggregator_mod, mld_protect_name => mld_s_hybrid_aggregator_build_tprol
use mld_s_inner_mod
implicit none
class(mld_s_hybrid_aggregator_type), target, intent(inout) :: ag
type(mld_sml_parms), intent(inout) :: parms
type(psb_sspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_sspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
character(len=20) :: name
integer(psb_mpik_) :: ictxt, np, me
integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ntaggr
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_s_hybrid_aggregator_tprol'
if (psb_get_errstatus().ne.0) return
call psb_erractionsave(err_act)
debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level()
info = psb_success_
ictxt = desc_a%get_context()
call psb_info(ictxt,me,np)
call mld_check_def(parms%ml_cycle,'Multilevel cycle',&
& mld_mult_ml_,is_legal_ml_cycle)
call mld_check_def(parms%par_aggr_alg,'Aggregation',&
& mld_dec_aggr_,is_legal_ml_par_aggr_alg)
call mld_check_def(parms%aggr_ord,'Ordering',&
& mld_aggr_ord_nat_,is_legal_ml_aggr_ord)
call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs)
call mld_s_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info)
if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
if (info /= psb_success_) then
info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='hyb_map_bld/map_to_tprol')
goto 9999
endif
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_s_hybrid_aggregator_build_tprol

@ -36,9 +36,9 @@
! !
! !
! !
! File: mld_s_vmb_map__bld.f90 ! File: mld_s_soc1_map__bld.f90
! !
! Subroutine: mld_s_vmb_map_bld ! Subroutine: mld_s_soc1_map_bld
! Version: real ! Version: real
! !
! This routine builds the tentative prolongator based on the ! This routine builds the tentative prolongator based on the
@ -67,11 +67,11 @@
! !
! !
! !
subroutine mld_s_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) subroutine mld_s_soc1_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
use psb_base_mod use psb_base_mod
use mld_base_prec_type use mld_base_prec_type
use mld_s_inner_mod!, mld_protect_name => mld_s_vmb_map_bld use mld_s_inner_mod!, mld_protect_name => mld_s_soc1_map_bld
implicit none implicit none
@ -98,7 +98,7 @@ subroutine mld_s_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
if (psb_get_errstatus() /= 0) return if (psb_get_errstatus() /= 0) return
info=psb_success_ info=psb_success_
name = 'mld_vmb_map_bld' name = 'mld_soc1_map_bld'
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
debug_unit = psb_get_debug_unit() debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level() debug_level = psb_get_debug_level()
@ -318,5 +318,5 @@ subroutine mld_s_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
return return
end subroutine mld_s_vmb_map_bld end subroutine mld_s_soc1_map_bld

@ -36,13 +36,13 @@
! !
! !
! !
! File: mld_s_hyb_map__bld.f90 ! File: mld_s_soc2_map__bld.f90
! !
! Subroutine: mld_s_hyb_map_bld ! Subroutine: mld_s_soc2_map_bld
! Version: real ! Version: real
! !
! The aggregator object hosts the aggregation method for building ! The aggregator object hosts the aggregation method for building
! the multilevel hierarchy. This variant is based on the hybrid method ! the multilevel hierarchy. This variant is based on the method
! presented in ! presented in
! !
! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: ! S. Gratton, P. Henon, P. Jiranek and X. Vasseur:
@ -66,11 +66,11 @@
! !
! !
! !
subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) subroutine mld_s_soc2_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
use psb_base_mod use psb_base_mod
use mld_base_prec_type use mld_base_prec_type
use mld_s_inner_mod!, mld_protect_name => mld_s_hyb_map_bld use mld_s_inner_mod!, mld_protect_name => mld_s_soc2_map_bld
implicit none implicit none
@ -98,7 +98,7 @@ subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
if (psb_get_errstatus() /= 0) return if (psb_get_errstatus() /= 0) return
info=psb_success_ info=psb_success_
name = 'mld_hyb_map_bld' name = 'mld_soc2_map_bld'
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
debug_unit = psb_get_debug_unit() debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level() debug_level = psb_get_debug_level()
@ -326,5 +326,5 @@ subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
return return
end subroutine mld_s_hyb_map_bld end subroutine mld_s_soc2_map_bld

@ -41,7 +41,7 @@
! Version: real ! Version: real
! !
! !
! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! This routine is mainly an interface to map_bld where the real work is performed.
! It takes care of some consistency checking, and calls map_to_tprol, which is ! It takes care of some consistency checking, and calls map_to_tprol, which is
! refactored and shared among all the aggregation methods that produce a simple ! refactored and shared among all the aggregation methods that produce a simple
! integer mapping. ! integer mapping.
@ -127,13 +127,13 @@ subroutine mld_s_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,
if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) call atmp%cscnv(info,type='CSR')
if (info == psb_success_) & if (info == psb_success_) &
& call mld_s_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) & call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info)
if (info == psb_success_) call atmp%free() if (info == psb_success_) call atmp%free()
if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
if (info /= psb_success_) then if (info /= psb_success_) then
info=psb_err_from_subroutine_ info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') call psb_errpush(info,name,a_err='map_bld/map_to_tprol')
goto 9999 goto 9999
endif endif

@ -40,7 +40,7 @@
! Subroutine: mld_z_dec_aggregator_tprol ! Subroutine: mld_z_dec_aggregator_tprol
! Version: complex ! Version: complex
! !
! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! This routine is mainly an interface to map_bld where the real work is performed.
! It takes care of some consistency checking, and calls map_to_tprol, which is ! It takes care of some consistency checking, and calls map_to_tprol, which is
! refactored and shared among all the aggregation methods that produce a simple ! refactored and shared among all the aggregation methods that produce a simple
! integer mapping. ! integer mapping.
@ -111,12 +111,11 @@ subroutine mld_z_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_
call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info)
!!$ call mld_z_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info)
if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
if (info /= psb_success_) then if (info /= psb_success_) then
info=psb_err_from_subroutine_ info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') call psb_errpush(info,name,a_err='map_bld/map_to_tprol')
goto 9999 goto 9999
endif endif

@ -1,130 +0,0 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
! File: mld_z_hybrid_aggregator_tprol.f90
!
! Subroutine: mld_z_hybrid_aggregator_tprol
! Version: complex
!
!
! This routine is mainly an interface to hyb_map_bld where the real work is performed.
! It takes care of some consistency checking, and calls map_to_tprol, which is
! refactored and shared among all the aggregation methods that produce a simple
! integer mapping.
!
!
! Arguments:
! p - type(mld_z_onelev_type), input/output.
! The 'one-level' data structure containing the control
! parameters and (eventually) coarse matrix and prolongator/restrictors.
!
! a - type(psb_zspmat_type).
! The sparse matrix structure containing the local part of the
! fine-level matrix.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of a.
! ilaggr - integer, dimension(:), allocatable, output
! The mapping between the row indices of the coarse-level
! matrix and the row indices of the fine-level matrix.
! ilaggr(i)=j means that node i in the adjacency graph
! of the fine-level matrix is mapped onto node j in the
! adjacency graph of the coarse-level matrix. Note that on exit the indices
! will be shifted so as to make sure the ranges on the various processes do not
! overlap.
! nlaggr - integer, dimension(:), allocatable, output
! nlaggr(i) contains the aggregates held by process i.
! op_prol - type(psb_zspmat_type), output
! The tentative prolongator, based on ilaggr.
!
! info - integer, output.
! Error code.
!
subroutine mld_z_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
use psb_base_mod
use mld_z_prec_type
use mld_z_hybrid_aggregator_mod, mld_protect_name => mld_z_hybrid_aggregator_build_tprol
use mld_z_inner_mod
implicit none
class(mld_z_hybrid_aggregator_type), target, intent(inout) :: ag
type(mld_dml_parms), intent(inout) :: parms
type(psb_zspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_zspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
character(len=20) :: name
integer(psb_mpik_) :: ictxt, np, me
integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ntaggr
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_z_hybrid_aggregator_tprol'
if (psb_get_errstatus().ne.0) return
call psb_erractionsave(err_act)
debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level()
info = psb_success_
ictxt = desc_a%get_context()
call psb_info(ictxt,me,np)
call mld_check_def(parms%ml_cycle,'Multilevel cycle',&
& mld_mult_ml_,is_legal_ml_cycle)
call mld_check_def(parms%par_aggr_alg,'Aggregation',&
& mld_dec_aggr_,is_legal_ml_par_aggr_alg)
call mld_check_def(parms%aggr_ord,'Ordering',&
& mld_aggr_ord_nat_,is_legal_ml_aggr_ord)
call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs)
call mld_z_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info)
if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
if (info /= psb_success_) then
info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='hyb_map_bld/map_to_tprol')
goto 9999
endif
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_z_hybrid_aggregator_build_tprol

@ -36,9 +36,9 @@
! !
! !
! !
! File: mld_z_vmb_map__bld.f90 ! File: mld_z_soc1_map__bld.f90
! !
! Subroutine: mld_z_vmb_map_bld ! Subroutine: mld_z_soc1_map_bld
! Version: complex ! Version: complex
! !
! This routine builds the tentative prolongator based on the ! This routine builds the tentative prolongator based on the
@ -67,11 +67,11 @@
! !
! !
! !
subroutine mld_z_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) subroutine mld_z_soc1_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
use psb_base_mod use psb_base_mod
use mld_base_prec_type use mld_base_prec_type
use mld_z_inner_mod!, mld_protect_name => mld_z_vmb_map_bld use mld_z_inner_mod!, mld_protect_name => mld_z_soc1_map_bld
implicit none implicit none
@ -98,7 +98,7 @@ subroutine mld_z_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
if (psb_get_errstatus() /= 0) return if (psb_get_errstatus() /= 0) return
info=psb_success_ info=psb_success_
name = 'mld_vmb_map_bld' name = 'mld_soc1_map_bld'
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
debug_unit = psb_get_debug_unit() debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level() debug_level = psb_get_debug_level()
@ -318,5 +318,5 @@ subroutine mld_z_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
return return
end subroutine mld_z_vmb_map_bld end subroutine mld_z_soc1_map_bld

@ -36,13 +36,13 @@
! !
! !
! !
! File: mld_z_hyb_map__bld.f90 ! File: mld_z_soc2_map__bld.f90
! !
! Subroutine: mld_z_hyb_map_bld ! Subroutine: mld_z_soc2_map_bld
! Version: complex ! Version: complex
! !
! The aggregator object hosts the aggregation method for building ! The aggregator object hosts the aggregation method for building
! the multilevel hierarchy. This variant is based on the hybrid method ! the multilevel hierarchy. This variant is based on the method
! presented in ! presented in
! !
! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: ! S. Gratton, P. Henon, P. Jiranek and X. Vasseur:
@ -66,11 +66,11 @@
! !
! !
! !
subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) subroutine mld_z_soc2_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
use psb_base_mod use psb_base_mod
use mld_base_prec_type use mld_base_prec_type
use mld_z_inner_mod!, mld_protect_name => mld_z_hyb_map_bld use mld_z_inner_mod!, mld_protect_name => mld_z_soc2_map_bld
implicit none implicit none
@ -98,7 +98,7 @@ subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
if (psb_get_errstatus() /= 0) return if (psb_get_errstatus() /= 0) return
info=psb_success_ info=psb_success_
name = 'mld_hyb_map_bld' name = 'mld_soc2_map_bld'
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
debug_unit = psb_get_debug_unit() debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level() debug_level = psb_get_debug_level()
@ -326,5 +326,5 @@ subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
return return
end subroutine mld_z_hyb_map_bld end subroutine mld_z_soc2_map_bld

@ -41,7 +41,7 @@
! Version: complex ! Version: complex
! !
! !
! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! This routine is mainly an interface to map_bld where the real work is performed.
! It takes care of some consistency checking, and calls map_to_tprol, which is ! It takes care of some consistency checking, and calls map_to_tprol, which is
! refactored and shared among all the aggregation methods that produce a simple ! refactored and shared among all the aggregation methods that produce a simple
! integer mapping. ! integer mapping.
@ -127,13 +127,13 @@ subroutine mld_z_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,
if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) call atmp%cscnv(info,type='CSR')
if (info == psb_success_) & if (info == psb_success_) &
& call mld_z_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) & call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info)
if (info == psb_success_) call atmp%free() if (info == psb_success_) call atmp%free()
if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
if (info /= psb_success_) then if (info /= psb_success_) then
info=psb_err_from_subroutine_ info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') call psb_errpush(info,name,a_err='map_bld/map_to_tprol')
goto 9999 goto 9999
endif endif

@ -234,8 +234,8 @@ module mld_base_prec_type
! Legal values for entry: mld_aggr_type_ ! Legal values for entry: mld_aggr_type_
! !
integer(psb_ipk_), parameter :: mld_noalg_ = 0 integer(psb_ipk_), parameter :: mld_noalg_ = 0
integer(psb_ipk_), parameter :: mld_vmb_ = 1 integer(psb_ipk_), parameter :: mld_soc1_ = 1
integer(psb_ipk_), parameter :: mld_hyb_ = 2 integer(psb_ipk_), parameter :: mld_soc2_ = 2
! !
! Legal values for entry: mld_aggr_prol_ ! Legal values for entry: mld_aggr_prol_
! !
@ -323,7 +323,7 @@ module mld_base_prec_type
& matrix_names(0:1)=(/'distributed ','replicated '/) & matrix_names(0:1)=(/'distributed ','replicated '/)
character(len=18), parameter, private :: & character(len=18), parameter, private :: &
& aggr_type_names(0:2)=(/'None ',& & aggr_type_names(0:2)=(/'None ',&
& 'VMB aggregation ', 'Hybrid aggregation'/) & 'SOC measure 1 ', 'SOC Measure 2 '/)
character(len=18), parameter, private :: & character(len=18), parameter, private :: &
& par_aggr_alg_names(0:2)=(/& & par_aggr_alg_names(0:2)=(/&
& 'decoupled aggr. ', 'sym. dec. aggr. ',& & 'decoupled aggr. ', 'sym. dec. aggr. ',&
@ -438,10 +438,10 @@ contains
val = mld_kcycle_ml_ val = mld_kcycle_ml_
case('KCYCLESYM') case('KCYCLESYM')
val = mld_kcyclesym_ml_ val = mld_kcyclesym_ml_
case('HYB') case('SOC2')
val = mld_hyb_ val = mld_soc2_
case('VMB') case('SOC1')
val = mld_vmb_ val = mld_soc1_
case('DEC') case('DEC')
val = mld_dec_aggr_ val = mld_dec_aggr_
case('SYMDEC') case('SYMDEC')
@ -774,7 +774,7 @@ contains
integer(psb_ipk_), intent(in) :: ip integer(psb_ipk_), intent(in) :: ip
logical :: is_legal_ml_aggr_type logical :: is_legal_ml_aggr_type
is_legal_ml_aggr_type = (ip >= mld_vmb_) .and. (ip <= mld_hyb_) is_legal_ml_aggr_type = (ip >= mld_soc1_) .and. (ip <= mld_soc2_)
return return
end function is_legal_ml_aggr_type end function is_legal_ml_aggr_type
function is_legal_ml_aggr_ord(ip) function is_legal_ml_aggr_ord(ip)

@ -114,7 +114,7 @@ module mld_c_dec_aggregator_mod
end subroutine mld_c_map_bld end subroutine mld_c_map_bld
end interface end interface
procedure(mld_c_map_bld) :: mld_c_vmb_map_bld, mld_c_hyb_map_bld procedure(mld_c_map_bld) :: mld_c_soc1_map_bld, mld_c_soc2_map_bld
interface interface
subroutine mld_c_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) subroutine mld_c_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
@ -161,13 +161,13 @@ contains
select case(parms%aggr_type) select case(parms%aggr_type)
case (mld_noalg_) case (mld_noalg_)
ag%map_bld => null() ag%map_bld => null()
case (mld_vmb_) case (mld_soc1_)
ag%map_bld => mld_c_vmb_map_bld ag%map_bld => mld_c_soc1_map_bld
case (mld_hyb_) case (mld_soc2_)
ag%map_bld => mld_c_hyb_map_bld ag%map_bld => mld_c_soc2_map_bld
case default case default
write(0,*) 'Unknown aggregation type, defaulting to VMB' write(0,*) 'Unknown aggregation type, defaulting to SOC1'
ag%map_bld => mld_c_vmb_map_bld ag%map_bld => mld_c_soc1_map_bld
end select end select
return return
@ -178,7 +178,7 @@ contains
implicit none implicit none
class(mld_c_dec_aggregator_type), intent(inout) :: ag class(mld_c_dec_aggregator_type), intent(inout) :: ag
ag%map_bld => mld_c_vmb_map_bld ag%map_bld => mld_c_soc1_map_bld
return return
end subroutine mld_c_dec_aggregator_default end subroutine mld_c_dec_aggregator_default

@ -489,7 +489,7 @@ contains
lv%parms%sweeps_pre = 1 lv%parms%sweeps_pre = 1
lv%parms%sweeps_post = 1 lv%parms%sweeps_post = 1
lv%parms%ml_cycle = mld_vcycle_ml_ lv%parms%ml_cycle = mld_vcycle_ml_
lv%parms%aggr_type = mld_vmb_ lv%parms%aggr_type = mld_soc1_
lv%parms%par_aggr_alg = mld_dec_aggr_ lv%parms%par_aggr_alg = mld_dec_aggr_
lv%parms%aggr_ord = mld_aggr_ord_nat_ lv%parms%aggr_ord = mld_aggr_ord_nat_
lv%parms%aggr_prol = mld_smooth_prol_ lv%parms%aggr_prol = mld_smooth_prol_

@ -114,7 +114,7 @@ module mld_d_dec_aggregator_mod
end subroutine mld_d_map_bld end subroutine mld_d_map_bld
end interface end interface
procedure(mld_d_map_bld) :: mld_d_vmb_map_bld, mld_d_hyb_map_bld procedure(mld_d_map_bld) :: mld_d_soc1_map_bld, mld_d_soc2_map_bld
interface interface
subroutine mld_d_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) subroutine mld_d_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
@ -161,13 +161,13 @@ contains
select case(parms%aggr_type) select case(parms%aggr_type)
case (mld_noalg_) case (mld_noalg_)
ag%map_bld => null() ag%map_bld => null()
case (mld_vmb_) case (mld_soc1_)
ag%map_bld => mld_d_vmb_map_bld ag%map_bld => mld_d_soc1_map_bld
case (mld_hyb_) case (mld_soc2_)
ag%map_bld => mld_d_hyb_map_bld ag%map_bld => mld_d_soc2_map_bld
case default case default
write(0,*) 'Unknown aggregation type, defaulting to VMB' write(0,*) 'Unknown aggregation type, defaulting to SOC1'
ag%map_bld => mld_d_vmb_map_bld ag%map_bld => mld_d_soc1_map_bld
end select end select
return return
@ -178,7 +178,7 @@ contains
implicit none implicit none
class(mld_d_dec_aggregator_type), intent(inout) :: ag class(mld_d_dec_aggregator_type), intent(inout) :: ag
ag%map_bld => mld_d_vmb_map_bld ag%map_bld => mld_d_soc1_map_bld
return return
end subroutine mld_d_dec_aggregator_default end subroutine mld_d_dec_aggregator_default

@ -489,7 +489,7 @@ contains
lv%parms%sweeps_pre = 1 lv%parms%sweeps_pre = 1
lv%parms%sweeps_post = 1 lv%parms%sweeps_post = 1
lv%parms%ml_cycle = mld_vcycle_ml_ lv%parms%ml_cycle = mld_vcycle_ml_
lv%parms%aggr_type = mld_vmb_ lv%parms%aggr_type = mld_soc1_
lv%parms%par_aggr_alg = mld_dec_aggr_ lv%parms%par_aggr_alg = mld_dec_aggr_
lv%parms%aggr_ord = mld_aggr_ord_nat_ lv%parms%aggr_ord = mld_aggr_ord_nat_
lv%parms%aggr_prol = mld_smooth_prol_ lv%parms%aggr_prol = mld_smooth_prol_

@ -114,7 +114,7 @@ module mld_s_dec_aggregator_mod
end subroutine mld_s_map_bld end subroutine mld_s_map_bld
end interface end interface
procedure(mld_s_map_bld) :: mld_s_vmb_map_bld, mld_s_hyb_map_bld procedure(mld_s_map_bld) :: mld_s_soc1_map_bld, mld_s_soc2_map_bld
interface interface
subroutine mld_s_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) subroutine mld_s_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
@ -161,13 +161,13 @@ contains
select case(parms%aggr_type) select case(parms%aggr_type)
case (mld_noalg_) case (mld_noalg_)
ag%map_bld => null() ag%map_bld => null()
case (mld_vmb_) case (mld_soc1_)
ag%map_bld => mld_s_vmb_map_bld ag%map_bld => mld_s_soc1_map_bld
case (mld_hyb_) case (mld_soc2_)
ag%map_bld => mld_s_hyb_map_bld ag%map_bld => mld_s_soc2_map_bld
case default case default
write(0,*) 'Unknown aggregation type, defaulting to VMB' write(0,*) 'Unknown aggregation type, defaulting to SOC1'
ag%map_bld => mld_s_vmb_map_bld ag%map_bld => mld_s_soc1_map_bld
end select end select
return return
@ -178,7 +178,7 @@ contains
implicit none implicit none
class(mld_s_dec_aggregator_type), intent(inout) :: ag class(mld_s_dec_aggregator_type), intent(inout) :: ag
ag%map_bld => mld_s_vmb_map_bld ag%map_bld => mld_s_soc1_map_bld
return return
end subroutine mld_s_dec_aggregator_default end subroutine mld_s_dec_aggregator_default

@ -489,7 +489,7 @@ contains
lv%parms%sweeps_pre = 1 lv%parms%sweeps_pre = 1
lv%parms%sweeps_post = 1 lv%parms%sweeps_post = 1
lv%parms%ml_cycle = mld_vcycle_ml_ lv%parms%ml_cycle = mld_vcycle_ml_
lv%parms%aggr_type = mld_vmb_ lv%parms%aggr_type = mld_soc1_
lv%parms%par_aggr_alg = mld_dec_aggr_ lv%parms%par_aggr_alg = mld_dec_aggr_
lv%parms%aggr_ord = mld_aggr_ord_nat_ lv%parms%aggr_ord = mld_aggr_ord_nat_
lv%parms%aggr_prol = mld_smooth_prol_ lv%parms%aggr_prol = mld_smooth_prol_

@ -114,7 +114,7 @@ module mld_z_dec_aggregator_mod
end subroutine mld_z_map_bld end subroutine mld_z_map_bld
end interface end interface
procedure(mld_z_map_bld) :: mld_z_vmb_map_bld, mld_z_hyb_map_bld procedure(mld_z_map_bld) :: mld_z_soc1_map_bld, mld_z_soc2_map_bld
interface interface
subroutine mld_z_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) subroutine mld_z_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
@ -161,13 +161,13 @@ contains
select case(parms%aggr_type) select case(parms%aggr_type)
case (mld_noalg_) case (mld_noalg_)
ag%map_bld => null() ag%map_bld => null()
case (mld_vmb_) case (mld_soc1_)
ag%map_bld => mld_z_vmb_map_bld ag%map_bld => mld_z_soc1_map_bld
case (mld_hyb_) case (mld_soc2_)
ag%map_bld => mld_z_hyb_map_bld ag%map_bld => mld_z_soc2_map_bld
case default case default
write(0,*) 'Unknown aggregation type, defaulting to VMB' write(0,*) 'Unknown aggregation type, defaulting to SOC1'
ag%map_bld => mld_z_vmb_map_bld ag%map_bld => mld_z_soc1_map_bld
end select end select
return return
@ -178,7 +178,7 @@ contains
implicit none implicit none
class(mld_z_dec_aggregator_type), intent(inout) :: ag class(mld_z_dec_aggregator_type), intent(inout) :: ag
ag%map_bld => mld_z_vmb_map_bld ag%map_bld => mld_z_soc1_map_bld
return return
end subroutine mld_z_dec_aggregator_default end subroutine mld_z_dec_aggregator_default

@ -489,7 +489,7 @@ contains
lv%parms%sweeps_pre = 1 lv%parms%sweeps_pre = 1
lv%parms%sweeps_post = 1 lv%parms%sweeps_post = 1
lv%parms%ml_cycle = mld_vcycle_ml_ lv%parms%ml_cycle = mld_vcycle_ml_
lv%parms%aggr_type = mld_vmb_ lv%parms%aggr_type = mld_soc1_
lv%parms%par_aggr_alg = mld_dec_aggr_ lv%parms%par_aggr_alg = mld_dec_aggr_
lv%parms%aggr_ord = mld_aggr_ord_nat_ lv%parms%aggr_ord = mld_aggr_ord_nat_
lv%parms%aggr_prol = mld_smooth_prol_ lv%parms%aggr_prol = mld_smooth_prol_

Loading…
Cancel
Save