Change interface of MAT_BLD adding desc_ac

unify_aggr_bld
Salvatore Filippone 5 years ago
parent dc03929a06
commit fb3a2cdbdd

@ -133,7 +133,8 @@
! info - integer, output.
! Error code.
!
subroutine mld_d_dec_aggregator_mat_bld(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info)
subroutine mld_d_dec_aggregator_mat_bld(ag,parms,a,desc_a,ilaggr,nlaggr,&
& ac,desc_ac,op_prol,op_restr,info)
use psb_base_mod
use mld_d_prec_type, mld_protect_name => mld_d_dec_aggregator_mat_bld
use mld_d_inner_mod
@ -146,6 +147,7 @@ subroutine mld_d_dec_aggregator_mat_bld(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_p
integer(psb_lpk_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_ldspmat_type), intent(inout) :: op_prol
type(psb_ldspmat_type), intent(out) :: ac,op_restr
type(psb_desc_type), intent(inout) :: desc_ac
integer(psb_ipk_), intent(out) :: info
! Local variables
@ -177,22 +179,22 @@ subroutine mld_d_dec_aggregator_mat_bld(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_p
case (mld_no_smooth_)
call mld_daggrmat_nosmth_bld(a,desc_a,ilaggr,nlaggr,&
& parms,ac,op_prol,op_restr,info)
& parms,ac,desc_ac,op_prol,op_restr,info)
case(mld_smooth_prol_)
call mld_daggrmat_smth_bld(a,desc_a,ilaggr,nlaggr, &
& parms,ac,op_prol,op_restr,info)
& parms,ac,desc_ac,op_prol,op_restr,info)
case(mld_biz_prol_)
call mld_daggrmat_biz_bld(a,desc_a,ilaggr,nlaggr, &
& parms,ac,op_prol,op_restr,info)
!!$ case(mld_biz_prol_)
!!$
!!$ call mld_daggrmat_biz_bld(a,desc_a,ilaggr,nlaggr, &
!!$ & parms,ac,desc_ac,op_prol,op_restr,info)
case(mld_min_energy_)
call mld_daggrmat_minnrg_bld(a,desc_a,ilaggr,nlaggr, &
& parms,ac,op_prol,op_restr,info)
& parms,ac,desc_ac,op_prol,op_restr,info)
case default
info = psb_err_internal_error_

@ -80,7 +80,7 @@
! info - integer, output.
! Error code.
!
subroutine mld_daggrmat_biz_bld(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_restr,info)
subroutine mld_daggrmat_biz_bld(a,desc_a,ilaggr,nlaggr,parms,ac,desc_ac,op_prol,op_restr,info)
use psb_base_mod
use mld_base_prec_type
use mld_d_inner_mod, mld_protect_name => mld_daggrmat_biz_bld
@ -95,6 +95,7 @@ subroutine mld_daggrmat_biz_bld(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_restr
type(mld_dml_parms), intent(inout) :: parms
type(psb_ldspmat_type), intent(inout) :: op_prol
type(psb_ldspmat_type), intent(out) :: ac,op_restr
type(psb_desc_type), intent(inout) :: desc_ac
integer(psb_ipk_), intent(out) :: info
! Local variables

@ -104,7 +104,8 @@
! Error code.
!
!
subroutine mld_daggrmat_minnrg_bld(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_restr,info)
subroutine mld_daggrmat_minnrg_bld(a,desc_a,ilaggr,nlaggr,parms,&
&ac,desc_ac,op_prol,op_restr,info)
use psb_base_mod
use mld_base_prec_type
use mld_d_inner_mod, mld_protect_name => mld_daggrmat_minnrg_bld
@ -118,6 +119,7 @@ subroutine mld_daggrmat_minnrg_bld(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_re
type(mld_dml_parms), intent(inout) :: parms
type(psb_ldspmat_type), intent(inout) :: op_prol
type(psb_ldspmat_type), intent(out) :: ac,op_restr
type(psb_desc_type), intent(inout) :: desc_ac
integer(psb_ipk_), intent(out) :: info
! Local variables

@ -96,7 +96,8 @@
! Error code.
!
!
subroutine mld_daggrmat_nosmth_bld(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_restr,info)
subroutine mld_daggrmat_nosmth_bld(a,desc_a,ilaggr,nlaggr,parms,&
& ac,desc_ac,op_prol,op_restr,info)
use psb_base_mod
use mld_base_prec_type
use mld_d_inner_mod, mld_protect_name => mld_daggrmat_nosmth_bld
@ -110,6 +111,7 @@ subroutine mld_daggrmat_nosmth_bld(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_re
type(mld_dml_parms), intent(inout) :: parms
type(psb_ldspmat_type), intent(inout) :: op_prol
type(psb_ldspmat_type), intent(out) :: ac,op_restr
type(psb_desc_type), intent(inout) :: desc_ac
integer(psb_ipk_), intent(out) :: info
! Local variables

@ -102,7 +102,8 @@
! info - integer, output.
! Error code.
!
subroutine mld_daggrmat_smth_bld(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_restr,info)
subroutine mld_daggrmat_smth_bld(a,desc_a,ilaggr,nlaggr,parms,&
& ac,desc_ac,op_prol,op_restr,info)
use psb_base_mod
use mld_base_prec_type
use mld_d_inner_mod, mld_protect_name => mld_daggrmat_smth_bld
@ -117,6 +118,7 @@ subroutine mld_daggrmat_smth_bld(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_rest
type(mld_dml_parms), intent(inout) :: parms
type(psb_ldspmat_type), intent(inout) :: op_prol
type(psb_ldspmat_type), intent(out) :: ac,op_restr
type(psb_desc_type), intent(inout) :: desc_ac
integer(psb_ipk_), intent(out) :: info
! Local variables

@ -141,7 +141,8 @@ subroutine mld_d_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
! the mapping defined by mld_aggrmap_bld and applying the aggregation
! algorithm specified by lv%iprcparm(mld_aggr_prol_)
!
call lv%aggr%mat_bld(lv%parms,a,desc_a,ilaggr,nlaggr,lac,op_prol,op_restr,info)
call lv%aggr%mat_bld(lv%parms,a,desc_a,ilaggr,nlaggr,&
& lac,lv%desc_ac,op_prol,op_restr,info)
if(info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmat_asb')

@ -369,8 +369,8 @@ contains
!! in many cases it is the transpose of the prolongator.
!! \param info Return code
!!
subroutine mld_d_base_aggregator_mat_bld(ag,parms,a,desc_a,ilaggr,nlaggr,ac,&
& op_prol,op_restr,info)
subroutine mld_d_base_aggregator_mat_bld(ag,parms,a,desc_a,ilaggr,nlaggr,&
& ac,desc_ac,op_prol,op_restr,info)
use psb_base_mod
implicit none
class(mld_d_base_aggregator_type), target, intent(inout) :: ag
@ -380,6 +380,7 @@ contains
integer(psb_lpk_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_ldspmat_type), intent(inout) :: op_prol
type(psb_ldspmat_type), intent(out) :: ac,op_restr
type(psb_desc_type), intent(inout) :: desc_ac
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act
character(len=20) :: name='d_base_aggregator_mat_bld'

@ -109,8 +109,8 @@ module mld_d_dec_aggregator_mod
end interface
interface
subroutine mld_d_dec_aggregator_mat_bld(ag,parms,a,desc_a,ilaggr,nlaggr,ac,&
& op_prol,op_restr,info)
subroutine mld_d_dec_aggregator_mat_bld(ag,parms,a,desc_a,ilaggr,nlaggr,&
& ac,desc_ac,op_prol,op_restr,info)
import :: mld_d_dec_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, &
& psb_ipk_, psb_lpk_, psb_ldspmat_type, mld_dml_parms
implicit none
@ -121,6 +121,7 @@ module mld_d_dec_aggregator_mod
integer(psb_lpk_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_ldspmat_type), intent(inout) :: op_prol
type(psb_ldspmat_type), intent(out) :: ac,op_restr
type(psb_desc_type), intent(inout) :: desc_ac
integer(psb_ipk_), intent(out) :: info
end subroutine mld_d_dec_aggregator_mat_bld
end interface

@ -109,7 +109,8 @@ module mld_d_inner_mod
end interface mld_map_to_tprol
abstract interface
subroutine mld_daggrmat_var_bld(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_restr,info)
subroutine mld_daggrmat_var_bld(a,desc_a,ilaggr,nlaggr,parms,&
& ac,desc_ac,op_prol,op_restr,info)
import :: psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_, psb_lpk_, psb_ldspmat_type
import :: mld_d_onelev_type, mld_dml_parms
implicit none
@ -119,6 +120,7 @@ module mld_d_inner_mod
type(mld_dml_parms), intent(inout) :: parms
type(psb_ldspmat_type), intent(inout) :: op_prol
type(psb_ldspmat_type), intent(out) :: ac,op_restr
type(psb_desc_type), intent(inout) :: desc_ac
integer(psb_ipk_), intent(out) :: info
end subroutine mld_daggrmat_var_bld
end interface

Loading…
Cancel
Save