Expand LPK treatment. Need to go back to PSBLAS and fix RXEXTD.

stopcriterion
Salvatore Filippone 7 years ago
parent 507db73ea4
commit 5e1b8f1ae4

@ -81,15 +81,15 @@ subroutine mld_c_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lcspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
character(len=20) :: name
integer(psb_mpk_) :: ictxt, np, me
integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ntaggr
integer(psb_lpk_) :: ntaggr
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_c_dec_aggregator_tprol'

@ -94,16 +94,16 @@ subroutine mld_c_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
! Arguments
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_cspmat_type), intent(out) :: op_prol
integer(psb_lpk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_lcspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m,naggrm1, naggrp1, ntaggr
type(psb_c_coo_sparse_mat) :: tmpcoo
type(psb_lc_coo_sparse_mat) :: tmpcoo
integer(psb_ipk_) :: debug_level, debug_unit,err_act
integer(psb_ipk_) :: ictxt,np,me
integer(psb_ipk_) :: nrow, ncol, n_ne
integer(psb_lpk_) :: nrow, ncol, n_ne
character(len=20) :: name, ch_err
if(psb_get_errstatus() /= 0) return

@ -84,8 +84,8 @@ subroutine mld_c_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lcspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
@ -93,7 +93,7 @@ subroutine mld_c_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,
character(len=20) :: name
integer(psb_mpk_) :: ictxt, np, me
integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ntaggr, nr
integer(psb_lpk_) :: ntaggr, nr
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_c_symdec_aggregator_tprol'

@ -81,15 +81,15 @@ subroutine mld_d_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_ldspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
character(len=20) :: name
integer(psb_mpk_) :: ictxt, np, me
integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ntaggr
integer(psb_lpk_) :: ntaggr
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_d_dec_aggregator_tprol'

@ -94,16 +94,16 @@ subroutine mld_d_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
! Arguments
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_dspmat_type), intent(out) :: op_prol
integer(psb_lpk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_ldspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m,naggrm1, naggrp1, ntaggr
type(psb_d_coo_sparse_mat) :: tmpcoo
type(psb_ld_coo_sparse_mat) :: tmpcoo
integer(psb_ipk_) :: debug_level, debug_unit,err_act
integer(psb_ipk_) :: ictxt,np,me
integer(psb_ipk_) :: nrow, ncol, n_ne
integer(psb_lpk_) :: nrow, ncol, n_ne
character(len=20) :: name, ch_err
if(psb_get_errstatus() /= 0) return

@ -84,8 +84,8 @@ subroutine mld_d_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_ldspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
@ -93,7 +93,7 @@ subroutine mld_d_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,
character(len=20) :: name
integer(psb_mpk_) :: ictxt, np, me
integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ntaggr, nr
integer(psb_lpk_) :: ntaggr, nr
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_d_symdec_aggregator_tprol'

@ -81,15 +81,15 @@ subroutine mld_s_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lsspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
character(len=20) :: name
integer(psb_mpk_) :: ictxt, np, me
integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ntaggr
integer(psb_lpk_) :: ntaggr
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_s_dec_aggregator_tprol'

@ -94,16 +94,16 @@ subroutine mld_s_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
! Arguments
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_sspmat_type), intent(out) :: op_prol
integer(psb_lpk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_lsspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m,naggrm1, naggrp1, ntaggr
type(psb_s_coo_sparse_mat) :: tmpcoo
type(psb_ls_coo_sparse_mat) :: tmpcoo
integer(psb_ipk_) :: debug_level, debug_unit,err_act
integer(psb_ipk_) :: ictxt,np,me
integer(psb_ipk_) :: nrow, ncol, n_ne
integer(psb_lpk_) :: nrow, ncol, n_ne
character(len=20) :: name, ch_err
if(psb_get_errstatus() /= 0) return

@ -84,8 +84,8 @@ subroutine mld_s_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lsspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
@ -93,7 +93,7 @@ subroutine mld_s_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,
character(len=20) :: name
integer(psb_mpk_) :: ictxt, np, me
integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ntaggr, nr
integer(psb_lpk_) :: ntaggr, nr
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_s_symdec_aggregator_tprol'

@ -81,15 +81,15 @@ subroutine mld_z_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lzspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
character(len=20) :: name
integer(psb_mpk_) :: ictxt, np, me
integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ntaggr
integer(psb_lpk_) :: ntaggr
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_z_dec_aggregator_tprol'

@ -94,16 +94,16 @@ subroutine mld_z_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
! Arguments
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_zspmat_type), intent(out) :: op_prol
integer(psb_lpk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_lzspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m,naggrm1, naggrp1, ntaggr
type(psb_z_coo_sparse_mat) :: tmpcoo
type(psb_lz_coo_sparse_mat) :: tmpcoo
integer(psb_ipk_) :: debug_level, debug_unit,err_act
integer(psb_ipk_) :: ictxt,np,me
integer(psb_ipk_) :: nrow, ncol, n_ne
integer(psb_lpk_) :: nrow, ncol, n_ne
character(len=20) :: name, ch_err
if(psb_get_errstatus() /= 0) return

@ -84,8 +84,8 @@ subroutine mld_z_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lzspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
! Local variables
@ -93,7 +93,7 @@ subroutine mld_z_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,
character(len=20) :: name
integer(psb_mpk_) :: ictxt, np, me
integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ntaggr, nr
integer(psb_lpk_) :: ntaggr, nr
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_z_symdec_aggregator_tprol'

@ -95,7 +95,7 @@ subroutine mld_c_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
class(mld_c_onelev_type), intent(inout), target :: lv
type(psb_cspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(inout) :: nlaggr(:)
integer(psb_lpk_), intent(inout) :: nlaggr(:)
integer(psb_lpk_), intent(inout) :: ilaggr(:)
type(psb_lcspmat_type), intent(inout) :: op_prol
integer(psb_ipk_), intent(out) :: info
@ -109,7 +109,8 @@ subroutine mld_c_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
type(psb_cspmat_type) :: ac
type(psb_lc_coo_sparse_mat) :: acoo, bcoo
type(psb_lc_csr_sparse_mat) :: acsr1
integer(psb_lpk_) :: nzl, ntaggr
integer(psb_lpk_) :: ntaggr, nr, nc
integer(psb_ipk_) :: nzl, inl
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_c_onelev_mat_asb'
@ -157,8 +158,14 @@ subroutine mld_c_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
call ac%mv_to(bcoo)
nzl = bcoo%get_nzeros()
if (info == psb_success_) call psb_cdall(ictxt,lv%desc_ac,info,nl=nlaggr(me+1))
inl = nlaggr(me+1)
if (inl < nlaggr(me+1)) then
info = psb_bad_int_cnv_
call psb_errpush(info,name,&
& e_err=(/nlaggr(me+1),inl*1_psb_lpk_/))
goto 9999
end if
if (info == psb_success_) call psb_cdall(ictxt,lv%desc_ac,info,nl=inl)
if (info == psb_success_) call psb_cdins(nzl,bcoo%ia,bcoo%ja,lv%desc_ac,info)
if (info == psb_success_) call psb_cdasb(lv%desc_ac,info)
if (info == psb_success_) call psb_glob_to_loc(bcoo%ia(1:nzl),lv%desc_ac,info,iact='I')
@ -192,7 +199,8 @@ subroutine mld_c_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
end if
call op_prol%mv_from(acsr1)
endif
call op_prol%set_ncols(lv%desc_ac%get_local_cols())
nc = lv%desc_ac%get_local_cols()
call op_prol%set_ncols(nc)
if (np>1) then
call op_restr%cscnv(info,type='coo',dupl=psb_dupl_add_)
@ -211,7 +219,8 @@ subroutine mld_c_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
!
! Clip to local rows.
!
call op_restr%set_nrows(lv%desc_ac%get_local_rows())
nr = lv%desc_ac%get_local_rows()
call op_restr%set_nrows(nr)
if (debug_level >= psb_debug_outer_) &
& write(debug_unit,*) me,' ',trim(name),&

@ -95,7 +95,7 @@ subroutine mld_d_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
class(mld_d_onelev_type), intent(inout), target :: lv
type(psb_dspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(inout) :: nlaggr(:)
integer(psb_lpk_), intent(inout) :: nlaggr(:)
integer(psb_lpk_), intent(inout) :: ilaggr(:)
type(psb_ldspmat_type), intent(inout) :: op_prol
integer(psb_ipk_), intent(out) :: info
@ -109,7 +109,8 @@ subroutine mld_d_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
type(psb_dspmat_type) :: ac
type(psb_ld_coo_sparse_mat) :: acoo, bcoo
type(psb_ld_csr_sparse_mat) :: acsr1
integer(psb_lpk_) :: nzl, ntaggr
integer(psb_lpk_) :: ntaggr, nr, nc
integer(psb_ipk_) :: nzl, inl
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_d_onelev_mat_asb'
@ -157,8 +158,14 @@ subroutine mld_d_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
call ac%mv_to(bcoo)
nzl = bcoo%get_nzeros()
if (info == psb_success_) call psb_cdall(ictxt,lv%desc_ac,info,nl=nlaggr(me+1))
inl = nlaggr(me+1)
if (inl < nlaggr(me+1)) then
info = psb_bad_int_cnv_
call psb_errpush(info,name,&
& e_err=(/nlaggr(me+1),inl*1_psb_lpk_/))
goto 9999
end if
if (info == psb_success_) call psb_cdall(ictxt,lv%desc_ac,info,nl=inl)
if (info == psb_success_) call psb_cdins(nzl,bcoo%ia,bcoo%ja,lv%desc_ac,info)
if (info == psb_success_) call psb_cdasb(lv%desc_ac,info)
if (info == psb_success_) call psb_glob_to_loc(bcoo%ia(1:nzl),lv%desc_ac,info,iact='I')
@ -192,7 +199,8 @@ subroutine mld_d_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
end if
call op_prol%mv_from(acsr1)
endif
call op_prol%set_ncols(lv%desc_ac%get_local_cols())
nc = lv%desc_ac%get_local_cols()
call op_prol%set_ncols(nc)
if (np>1) then
call op_restr%cscnv(info,type='coo',dupl=psb_dupl_add_)
@ -211,7 +219,8 @@ subroutine mld_d_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
!
! Clip to local rows.
!
call op_restr%set_nrows(lv%desc_ac%get_local_rows())
nr = lv%desc_ac%get_local_rows()
call op_restr%set_nrows(nr)
if (debug_level >= psb_debug_outer_) &
& write(debug_unit,*) me,' ',trim(name),&

@ -95,7 +95,7 @@ subroutine mld_s_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
class(mld_s_onelev_type), intent(inout), target :: lv
type(psb_sspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(inout) :: nlaggr(:)
integer(psb_lpk_), intent(inout) :: nlaggr(:)
integer(psb_lpk_), intent(inout) :: ilaggr(:)
type(psb_lsspmat_type), intent(inout) :: op_prol
integer(psb_ipk_), intent(out) :: info
@ -109,7 +109,8 @@ subroutine mld_s_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
type(psb_sspmat_type) :: ac
type(psb_ls_coo_sparse_mat) :: acoo, bcoo
type(psb_ls_csr_sparse_mat) :: acsr1
integer(psb_lpk_) :: nzl, ntaggr
integer(psb_lpk_) :: ntaggr, nr, nc
integer(psb_ipk_) :: nzl, inl
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_s_onelev_mat_asb'
@ -157,8 +158,14 @@ subroutine mld_s_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
call ac%mv_to(bcoo)
nzl = bcoo%get_nzeros()
if (info == psb_success_) call psb_cdall(ictxt,lv%desc_ac,info,nl=nlaggr(me+1))
inl = nlaggr(me+1)
if (inl < nlaggr(me+1)) then
info = psb_bad_int_cnv_
call psb_errpush(info,name,&
& e_err=(/nlaggr(me+1),inl*1_psb_lpk_/))
goto 9999
end if
if (info == psb_success_) call psb_cdall(ictxt,lv%desc_ac,info,nl=inl)
if (info == psb_success_) call psb_cdins(nzl,bcoo%ia,bcoo%ja,lv%desc_ac,info)
if (info == psb_success_) call psb_cdasb(lv%desc_ac,info)
if (info == psb_success_) call psb_glob_to_loc(bcoo%ia(1:nzl),lv%desc_ac,info,iact='I')
@ -192,7 +199,8 @@ subroutine mld_s_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
end if
call op_prol%mv_from(acsr1)
endif
call op_prol%set_ncols(lv%desc_ac%get_local_cols())
nc = lv%desc_ac%get_local_cols()
call op_prol%set_ncols(nc)
if (np>1) then
call op_restr%cscnv(info,type='coo',dupl=psb_dupl_add_)
@ -211,7 +219,8 @@ subroutine mld_s_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
!
! Clip to local rows.
!
call op_restr%set_nrows(lv%desc_ac%get_local_rows())
nr = lv%desc_ac%get_local_rows()
call op_restr%set_nrows(nr)
if (debug_level >= psb_debug_outer_) &
& write(debug_unit,*) me,' ',trim(name),&

@ -95,7 +95,7 @@ subroutine mld_z_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
class(mld_z_onelev_type), intent(inout), target :: lv
type(psb_zspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(inout) :: nlaggr(:)
integer(psb_lpk_), intent(inout) :: nlaggr(:)
integer(psb_lpk_), intent(inout) :: ilaggr(:)
type(psb_lzspmat_type), intent(inout) :: op_prol
integer(psb_ipk_), intent(out) :: info
@ -109,7 +109,8 @@ subroutine mld_z_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
type(psb_zspmat_type) :: ac
type(psb_lz_coo_sparse_mat) :: acoo, bcoo
type(psb_lz_csr_sparse_mat) :: acsr1
integer(psb_lpk_) :: nzl, ntaggr
integer(psb_lpk_) :: ntaggr, nr, nc
integer(psb_ipk_) :: nzl, inl
integer(psb_ipk_) :: debug_level, debug_unit
name='mld_z_onelev_mat_asb'
@ -157,8 +158,14 @@ subroutine mld_z_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
call ac%mv_to(bcoo)
nzl = bcoo%get_nzeros()
if (info == psb_success_) call psb_cdall(ictxt,lv%desc_ac,info,nl=nlaggr(me+1))
inl = nlaggr(me+1)
if (inl < nlaggr(me+1)) then
info = psb_bad_int_cnv_
call psb_errpush(info,name,&
& e_err=(/nlaggr(me+1),inl*1_psb_lpk_/))
goto 9999
end if
if (info == psb_success_) call psb_cdall(ictxt,lv%desc_ac,info,nl=inl)
if (info == psb_success_) call psb_cdins(nzl,bcoo%ia,bcoo%ja,lv%desc_ac,info)
if (info == psb_success_) call psb_cdasb(lv%desc_ac,info)
if (info == psb_success_) call psb_glob_to_loc(bcoo%ia(1:nzl),lv%desc_ac,info,iact='I')
@ -192,7 +199,8 @@ subroutine mld_z_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
end if
call op_prol%mv_from(acsr1)
endif
call op_prol%set_ncols(lv%desc_ac%get_local_cols())
nc = lv%desc_ac%get_local_cols()
call op_prol%set_ncols(nc)
if (np>1) then
call op_restr%cscnv(info,type='coo',dupl=psb_dupl_add_)
@ -211,7 +219,8 @@ subroutine mld_z_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
!
! Clip to local rows.
!
call op_restr%set_nrows(lv%desc_ac%get_local_rows())
nr = lv%desc_ac%get_local_rows()
call op_restr%set_nrows(nr)
if (debug_level >= psb_debug_outer_) &
& write(debug_unit,*) me,' ',trim(name),&

@ -86,8 +86,8 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info)
& base_sm2, med_sm2, coarse_sm2
class(mld_c_base_aggregator_type), allocatable :: tmp_aggr
type(mld_sml_parms) :: baseparms, medparms, coarseparms
integer(psb_ipk_), allocatable :: ilaggr(:), nlaggr(:)
type(psb_cspmat_type) :: op_prol
integer(psb_lpk_), allocatable :: ilaggr(:), nlaggr(:)
type(psb_lcspmat_type) :: op_prol
type(mld_c_onelev_type), allocatable :: tprecv(:)
integer(psb_ipk_) :: int_err(5)
integer(psb_ipk_) :: debug_level, debug_unit

@ -86,8 +86,8 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info)
& base_sm2, med_sm2, coarse_sm2
class(mld_d_base_aggregator_type), allocatable :: tmp_aggr
type(mld_dml_parms) :: baseparms, medparms, coarseparms
integer(psb_ipk_), allocatable :: ilaggr(:), nlaggr(:)
type(psb_dspmat_type) :: op_prol
integer(psb_lpk_), allocatable :: ilaggr(:), nlaggr(:)
type(psb_ldspmat_type) :: op_prol
type(mld_d_onelev_type), allocatable :: tprecv(:)
integer(psb_ipk_) :: int_err(5)
integer(psb_ipk_) :: debug_level, debug_unit

@ -86,8 +86,8 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info)
& base_sm2, med_sm2, coarse_sm2
class(mld_s_base_aggregator_type), allocatable :: tmp_aggr
type(mld_sml_parms) :: baseparms, medparms, coarseparms
integer(psb_ipk_), allocatable :: ilaggr(:), nlaggr(:)
type(psb_sspmat_type) :: op_prol
integer(psb_lpk_), allocatable :: ilaggr(:), nlaggr(:)
type(psb_lsspmat_type) :: op_prol
type(mld_s_onelev_type), allocatable :: tprecv(:)
integer(psb_ipk_) :: int_err(5)
integer(psb_ipk_) :: debug_level, debug_unit

@ -86,8 +86,8 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info)
& base_sm2, med_sm2, coarse_sm2
class(mld_z_base_aggregator_type), allocatable :: tmp_aggr
type(mld_dml_parms) :: baseparms, medparms, coarseparms
integer(psb_ipk_), allocatable :: ilaggr(:), nlaggr(:)
type(psb_zspmat_type) :: op_prol
integer(psb_lpk_), allocatable :: ilaggr(:), nlaggr(:)
type(psb_lzspmat_type) :: op_prol
type(mld_z_onelev_type), allocatable :: tprecv(:)
integer(psb_ipk_) :: int_err(5)
integer(psb_ipk_) :: debug_level, debug_unit

@ -49,9 +49,9 @@
module mld_c_base_aggregator_mod
use mld_base_prec_type, only : mld_sml_parms
use psb_base_mod, only : psb_cspmat_type, psb_c_vect_type, &
use psb_base_mod, only : psb_cspmat_type, psb_lcspmat_type, psb_c_vect_type, &
& psb_c_base_vect_type, psb_clinmap_type, psb_spk_, &
& psb_ipk_, psb_epk_, psb_desc_type, psb_i_base_vect_type, &
& psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, &
& psb_erractionsave, psb_error_handler, psb_success_
!
! sm - class(mld_T_base_smoother_type), allocatable
@ -192,8 +192,8 @@ contains
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lcspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act
@ -223,8 +223,8 @@ contains
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_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_cspmat_type), intent(inout) :: op_prol
integer(psb_lpk_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_lcspmat_type), intent(inout) :: op_prol
type(psb_cspmat_type), intent(out) :: ac,op_restr
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act

@ -103,13 +103,13 @@ module mld_c_dec_aggregator_mod
abstract interface
subroutine mld_c_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
import :: psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_
import :: psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_, psb_lpk_
implicit none
integer(psb_ipk_), intent(in) :: iorder
type(psb_cspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
real(psb_spk_), intent(in) :: theta
integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
integer(psb_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
integer(psb_ipk_), intent(out) :: info
end subroutine mld_c_map_bld
end interface
@ -119,14 +119,14 @@ module mld_c_dec_aggregator_mod
interface
subroutine mld_c_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
import :: mld_c_dec_aggregator_type, psb_desc_type, psb_cspmat_type, psb_spk_, &
& psb_ipk_, psb_epk_, mld_sml_parms
& psb_ipk_, psb_lpk_, psb_lcspmat_type, mld_sml_parms
implicit none
class(mld_c_dec_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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lcspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_c_dec_aggregator_build_tprol
end interface
@ -135,14 +135,14 @@ module mld_c_dec_aggregator_mod
subroutine mld_c_dec_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,&
& op_prol,op_restr,info)
import :: mld_c_dec_aggregator_type, psb_desc_type, psb_cspmat_type, psb_spk_, &
& psb_ipk_, psb_epk_, mld_sml_parms
& psb_ipk_, psb_lpk_, psb_lcspmat_type, mld_sml_parms
implicit none
class(mld_c_dec_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_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_cspmat_type), intent(inout) :: op_prol
integer(psb_lpk_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_lcspmat_type), intent(inout) :: op_prol
type(psb_cspmat_type), intent(out) :: ac,op_restr
integer(psb_ipk_), intent(out) :: info
end subroutine mld_c_dec_aggregator_mat_asb

@ -125,12 +125,12 @@ module mld_c_inner_mod
interface mld_map_to_tprol
subroutine mld_c_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
use psb_base_mod, only : psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_
use psb_base_mod, only : psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_, psb_lpk_, psb_lcspmat_type
use mld_c_prec_type, only : mld_c_onelev_type
implicit none
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_cspmat_type), intent(out) :: op_prol
integer(psb_lpk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_lcspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_c_map_to_tprol
end interface mld_map_to_tprol

@ -57,8 +57,8 @@ module mld_c_onelev_mod
use mld_c_base_smoother_mod
use mld_c_dec_aggregator_mod
use psb_base_mod, only : psb_cspmat_type, psb_c_vect_type, &
& psb_c_base_vect_type, psb_clinmap_type, psb_spk_, &
& psb_ipk_, psb_epk_, psb_desc_type, psb_i_base_vect_type, &
& psb_c_base_vect_type, psb_lcspmat_type, psb_clinmap_type, psb_spk_, &
& psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, &
& psb_erractionsave, psb_error_handler
!
!
@ -147,7 +147,7 @@ module mld_c_onelev_mod
type(psb_desc_type) :: desc_ac
type(psb_cspmat_type), pointer :: base_a => null()
type(psb_desc_type), pointer :: base_desc => null()
type(psb_cspmat_type) :: tprol
type(psb_lcspmat_type) :: tprol
type(psb_clinmap_type) :: map
real(psb_spk_) :: szratio
contains
@ -197,14 +197,14 @@ module mld_c_onelev_mod
interface
subroutine mld_c_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
import :: psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_
import :: psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_, psb_lcspmat_type, psb_lpk_
import :: mld_c_onelev_type
implicit none
class(mld_c_onelev_type), intent(inout), target :: lv
type(psb_cspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_cspmat_type), intent(inout) :: op_prol
integer(psb_lpk_), intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_lcspmat_type), intent(inout) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_c_base_onelev_mat_asb
end interface
@ -519,8 +519,8 @@ contains
class(mld_c_onelev_type), intent(inout), target :: lv
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lcspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
call lv%aggr%bld_tprol(lv%parms,a,desc_a,ilaggr,nlaggr,op_prol,info)

@ -102,14 +102,14 @@ module mld_c_symdec_aggregator_mod
interface
subroutine mld_c_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
import :: mld_c_symdec_aggregator_type, psb_desc_type, psb_cspmat_type, psb_spk_, &
& psb_ipk_, psb_epk_, mld_sml_parms
& psb_ipk_, psb_lpk_, psb_lcspmat_type, mld_sml_parms
implicit none
class(mld_c_symdec_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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lcspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_c_symdec_aggregator_build_tprol
end interface

@ -49,9 +49,9 @@
module mld_d_base_aggregator_mod
use mld_base_prec_type, only : mld_dml_parms
use psb_base_mod, only : psb_dspmat_type, psb_d_vect_type, &
use psb_base_mod, only : psb_dspmat_type, psb_ldspmat_type, psb_d_vect_type, &
& psb_d_base_vect_type, psb_dlinmap_type, psb_dpk_, &
& psb_ipk_, psb_epk_, psb_desc_type, psb_i_base_vect_type, &
& psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, &
& psb_erractionsave, psb_error_handler, psb_success_
!
! sm - class(mld_T_base_smoother_type), allocatable
@ -192,8 +192,8 @@ contains
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_ldspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act
@ -223,8 +223,8 @@ contains
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_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_dspmat_type), intent(inout) :: op_prol
integer(psb_lpk_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_ldspmat_type), intent(inout) :: op_prol
type(psb_dspmat_type), intent(out) :: ac,op_restr
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act

@ -103,13 +103,13 @@ module mld_d_dec_aggregator_mod
abstract interface
subroutine mld_d_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
import :: psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_
import :: psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_, psb_lpk_
implicit none
integer(psb_ipk_), intent(in) :: iorder
type(psb_dspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
real(psb_dpk_), intent(in) :: theta
integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
integer(psb_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
integer(psb_ipk_), intent(out) :: info
end subroutine mld_d_map_bld
end interface
@ -119,14 +119,14 @@ module mld_d_dec_aggregator_mod
interface
subroutine mld_d_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
import :: mld_d_dec_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, &
& psb_ipk_, psb_epk_, mld_dml_parms
& psb_ipk_, psb_lpk_, psb_ldspmat_type, mld_dml_parms
implicit none
class(mld_d_dec_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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_ldspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_d_dec_aggregator_build_tprol
end interface
@ -135,14 +135,14 @@ module mld_d_dec_aggregator_mod
subroutine mld_d_dec_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,&
& op_prol,op_restr,info)
import :: mld_d_dec_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, &
& psb_ipk_, psb_epk_, mld_dml_parms
& psb_ipk_, psb_lpk_, psb_ldspmat_type, mld_dml_parms
implicit none
class(mld_d_dec_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_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_dspmat_type), intent(inout) :: op_prol
integer(psb_lpk_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_ldspmat_type), intent(inout) :: op_prol
type(psb_dspmat_type), intent(out) :: ac,op_restr
integer(psb_ipk_), intent(out) :: info
end subroutine mld_d_dec_aggregator_mat_asb

@ -125,12 +125,12 @@ module mld_d_inner_mod
interface mld_map_to_tprol
subroutine mld_d_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
use psb_base_mod, only : psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_
use psb_base_mod, only : psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_, psb_lpk_, psb_ldspmat_type
use mld_d_prec_type, only : mld_d_onelev_type
implicit none
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_dspmat_type), intent(out) :: op_prol
integer(psb_lpk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_ldspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_d_map_to_tprol
end interface mld_map_to_tprol

@ -57,8 +57,8 @@ module mld_d_onelev_mod
use mld_d_base_smoother_mod
use mld_d_dec_aggregator_mod
use psb_base_mod, only : psb_dspmat_type, psb_d_vect_type, &
& psb_d_base_vect_type, psb_dlinmap_type, psb_dpk_, &
& psb_ipk_, psb_epk_, psb_desc_type, psb_i_base_vect_type, &
& psb_d_base_vect_type, psb_ldspmat_type, psb_dlinmap_type, psb_dpk_, &
& psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, &
& psb_erractionsave, psb_error_handler
!
!
@ -147,7 +147,7 @@ module mld_d_onelev_mod
type(psb_desc_type) :: desc_ac
type(psb_dspmat_type), pointer :: base_a => null()
type(psb_desc_type), pointer :: base_desc => null()
type(psb_dspmat_type) :: tprol
type(psb_ldspmat_type) :: tprol
type(psb_dlinmap_type) :: map
real(psb_dpk_) :: szratio
contains
@ -197,14 +197,14 @@ module mld_d_onelev_mod
interface
subroutine mld_d_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
import :: psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_
import :: psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_, psb_ldspmat_type, psb_lpk_
import :: mld_d_onelev_type
implicit none
class(mld_d_onelev_type), intent(inout), target :: lv
type(psb_dspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_dspmat_type), intent(inout) :: op_prol
integer(psb_lpk_), intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_ldspmat_type), intent(inout) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_d_base_onelev_mat_asb
end interface
@ -519,8 +519,8 @@ contains
class(mld_d_onelev_type), intent(inout), target :: lv
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_ldspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
call lv%aggr%bld_tprol(lv%parms,a,desc_a,ilaggr,nlaggr,op_prol,info)

@ -53,6 +53,7 @@ module mld_d_sludist_solver
use mld_d_base_solver_mod
#if defined(LPK8)
type, extends(mld_d_base_solver_type) :: mld_d_sludist_solver_type
end type mld_d_sludist_solver_type

@ -102,14 +102,14 @@ module mld_d_symdec_aggregator_mod
interface
subroutine mld_d_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
import :: mld_d_symdec_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, &
& psb_ipk_, psb_epk_, mld_dml_parms
& psb_ipk_, psb_lpk_, psb_ldspmat_type, mld_dml_parms
implicit none
class(mld_d_symdec_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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_ldspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_d_symdec_aggregator_build_tprol
end interface

@ -49,9 +49,9 @@
module mld_s_base_aggregator_mod
use mld_base_prec_type, only : mld_sml_parms
use psb_base_mod, only : psb_sspmat_type, psb_s_vect_type, &
use psb_base_mod, only : psb_sspmat_type, psb_lsspmat_type, psb_s_vect_type, &
& psb_s_base_vect_type, psb_slinmap_type, psb_spk_, &
& psb_ipk_, psb_epk_, psb_desc_type, psb_i_base_vect_type, &
& psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, &
& psb_erractionsave, psb_error_handler, psb_success_
!
! sm - class(mld_T_base_smoother_type), allocatable
@ -192,8 +192,8 @@ contains
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lsspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act
@ -223,8 +223,8 @@ contains
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_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_sspmat_type), intent(inout) :: op_prol
integer(psb_lpk_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_lsspmat_type), intent(inout) :: op_prol
type(psb_sspmat_type), intent(out) :: ac,op_restr
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act

@ -103,13 +103,13 @@ module mld_s_dec_aggregator_mod
abstract interface
subroutine mld_s_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
import :: psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_
import :: psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_, psb_lpk_
implicit none
integer(psb_ipk_), intent(in) :: iorder
type(psb_sspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
real(psb_spk_), intent(in) :: theta
integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
integer(psb_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
integer(psb_ipk_), intent(out) :: info
end subroutine mld_s_map_bld
end interface
@ -119,14 +119,14 @@ module mld_s_dec_aggregator_mod
interface
subroutine mld_s_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
import :: mld_s_dec_aggregator_type, psb_desc_type, psb_sspmat_type, psb_spk_, &
& psb_ipk_, psb_epk_, mld_sml_parms
& psb_ipk_, psb_lpk_, psb_lsspmat_type, mld_sml_parms
implicit none
class(mld_s_dec_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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lsspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_s_dec_aggregator_build_tprol
end interface
@ -135,14 +135,14 @@ module mld_s_dec_aggregator_mod
subroutine mld_s_dec_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,&
& op_prol,op_restr,info)
import :: mld_s_dec_aggregator_type, psb_desc_type, psb_sspmat_type, psb_spk_, &
& psb_ipk_, psb_epk_, mld_sml_parms
& psb_ipk_, psb_lpk_, psb_lsspmat_type, mld_sml_parms
implicit none
class(mld_s_dec_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_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_sspmat_type), intent(inout) :: op_prol
integer(psb_lpk_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_lsspmat_type), intent(inout) :: op_prol
type(psb_sspmat_type), intent(out) :: ac,op_restr
integer(psb_ipk_), intent(out) :: info
end subroutine mld_s_dec_aggregator_mat_asb

@ -125,12 +125,12 @@ module mld_s_inner_mod
interface mld_map_to_tprol
subroutine mld_s_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
use psb_base_mod, only : psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_
use psb_base_mod, only : psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_, psb_lpk_, psb_lsspmat_type
use mld_s_prec_type, only : mld_s_onelev_type
implicit none
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_sspmat_type), intent(out) :: op_prol
integer(psb_lpk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_lsspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_s_map_to_tprol
end interface mld_map_to_tprol

@ -57,8 +57,8 @@ module mld_s_onelev_mod
use mld_s_base_smoother_mod
use mld_s_dec_aggregator_mod
use psb_base_mod, only : psb_sspmat_type, psb_s_vect_type, &
& psb_s_base_vect_type, psb_slinmap_type, psb_spk_, &
& psb_ipk_, psb_epk_, psb_desc_type, psb_i_base_vect_type, &
& psb_s_base_vect_type, psb_lsspmat_type, psb_slinmap_type, psb_spk_, &
& psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, &
& psb_erractionsave, psb_error_handler
!
!
@ -147,7 +147,7 @@ module mld_s_onelev_mod
type(psb_desc_type) :: desc_ac
type(psb_sspmat_type), pointer :: base_a => null()
type(psb_desc_type), pointer :: base_desc => null()
type(psb_sspmat_type) :: tprol
type(psb_lsspmat_type) :: tprol
type(psb_slinmap_type) :: map
real(psb_spk_) :: szratio
contains
@ -197,14 +197,14 @@ module mld_s_onelev_mod
interface
subroutine mld_s_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
import :: psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_
import :: psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_, psb_lsspmat_type, psb_lpk_
import :: mld_s_onelev_type
implicit none
class(mld_s_onelev_type), intent(inout), target :: lv
type(psb_sspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_sspmat_type), intent(inout) :: op_prol
integer(psb_lpk_), intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_lsspmat_type), intent(inout) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_s_base_onelev_mat_asb
end interface
@ -519,8 +519,8 @@ contains
class(mld_s_onelev_type), intent(inout), target :: lv
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lsspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
call lv%aggr%bld_tprol(lv%parms,a,desc_a,ilaggr,nlaggr,op_prol,info)

@ -102,14 +102,14 @@ module mld_s_symdec_aggregator_mod
interface
subroutine mld_s_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
import :: mld_s_symdec_aggregator_type, psb_desc_type, psb_sspmat_type, psb_spk_, &
& psb_ipk_, psb_epk_, mld_sml_parms
& psb_ipk_, psb_lpk_, psb_lsspmat_type, mld_sml_parms
implicit none
class(mld_s_symdec_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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lsspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_s_symdec_aggregator_build_tprol
end interface

@ -49,9 +49,9 @@
module mld_z_base_aggregator_mod
use mld_base_prec_type, only : mld_dml_parms
use psb_base_mod, only : psb_zspmat_type, psb_z_vect_type, &
use psb_base_mod, only : psb_zspmat_type, psb_lzspmat_type, psb_z_vect_type, &
& psb_z_base_vect_type, psb_zlinmap_type, psb_dpk_, &
& psb_ipk_, psb_epk_, psb_desc_type, psb_i_base_vect_type, &
& psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, &
& psb_erractionsave, psb_error_handler, psb_success_
!
! sm - class(mld_T_base_smoother_type), allocatable
@ -192,8 +192,8 @@ contains
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lzspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act
@ -223,8 +223,8 @@ contains
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_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_zspmat_type), intent(inout) :: op_prol
integer(psb_lpk_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_lzspmat_type), intent(inout) :: op_prol
type(psb_zspmat_type), intent(out) :: ac,op_restr
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act

@ -103,13 +103,13 @@ module mld_z_dec_aggregator_mod
abstract interface
subroutine mld_z_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info)
import :: psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_
import :: psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_, psb_lpk_
implicit none
integer(psb_ipk_), intent(in) :: iorder
type(psb_zspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
real(psb_dpk_), intent(in) :: theta
integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
integer(psb_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
integer(psb_ipk_), intent(out) :: info
end subroutine mld_z_map_bld
end interface
@ -119,14 +119,14 @@ module mld_z_dec_aggregator_mod
interface
subroutine mld_z_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
import :: mld_z_dec_aggregator_type, psb_desc_type, psb_zspmat_type, psb_dpk_, &
& psb_ipk_, psb_epk_, mld_dml_parms
& psb_ipk_, psb_lpk_, psb_lzspmat_type, mld_dml_parms
implicit none
class(mld_z_dec_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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lzspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_z_dec_aggregator_build_tprol
end interface
@ -135,14 +135,14 @@ module mld_z_dec_aggregator_mod
subroutine mld_z_dec_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,&
& op_prol,op_restr,info)
import :: mld_z_dec_aggregator_type, psb_desc_type, psb_zspmat_type, psb_dpk_, &
& psb_ipk_, psb_epk_, mld_dml_parms
& psb_ipk_, psb_lpk_, psb_lzspmat_type, mld_dml_parms
implicit none
class(mld_z_dec_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_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_zspmat_type), intent(inout) :: op_prol
integer(psb_lpk_), intent(inout) :: ilaggr(:), nlaggr(:)
type(psb_lzspmat_type), intent(inout) :: op_prol
type(psb_zspmat_type), intent(out) :: ac,op_restr
integer(psb_ipk_), intent(out) :: info
end subroutine mld_z_dec_aggregator_mat_asb

@ -125,12 +125,12 @@ module mld_z_inner_mod
interface mld_map_to_tprol
subroutine mld_z_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info)
use psb_base_mod, only : psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_
use psb_base_mod, only : psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_, psb_lpk_, psb_lzspmat_type
use mld_z_prec_type, only : mld_z_onelev_type
implicit none
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_zspmat_type), intent(out) :: op_prol
integer(psb_lpk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_lzspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_z_map_to_tprol
end interface mld_map_to_tprol

@ -57,8 +57,8 @@ module mld_z_onelev_mod
use mld_z_base_smoother_mod
use mld_z_dec_aggregator_mod
use psb_base_mod, only : psb_zspmat_type, psb_z_vect_type, &
& psb_z_base_vect_type, psb_zlinmap_type, psb_dpk_, &
& psb_ipk_, psb_epk_, psb_desc_type, psb_i_base_vect_type, &
& psb_z_base_vect_type, psb_lzspmat_type, psb_zlinmap_type, psb_dpk_, &
& psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, &
& psb_erractionsave, psb_error_handler
!
!
@ -147,7 +147,7 @@ module mld_z_onelev_mod
type(psb_desc_type) :: desc_ac
type(psb_zspmat_type), pointer :: base_a => null()
type(psb_desc_type), pointer :: base_desc => null()
type(psb_zspmat_type) :: tprol
type(psb_lzspmat_type) :: tprol
type(psb_zlinmap_type) :: map
real(psb_dpk_) :: szratio
contains
@ -197,14 +197,14 @@ module mld_z_onelev_mod
interface
subroutine mld_z_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info)
import :: psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_
import :: psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_, psb_lzspmat_type, psb_lpk_
import :: mld_z_onelev_type
implicit none
class(mld_z_onelev_type), intent(inout), target :: lv
type(psb_zspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_zspmat_type), intent(inout) :: op_prol
integer(psb_lpk_), intent(inout) :: ilaggr(:),nlaggr(:)
type(psb_lzspmat_type), intent(inout) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_z_base_onelev_mat_asb
end interface
@ -519,8 +519,8 @@ contains
class(mld_z_onelev_type), intent(inout), target :: lv
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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lzspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
call lv%aggr%bld_tprol(lv%parms,a,desc_a,ilaggr,nlaggr,op_prol,info)

@ -53,6 +53,7 @@ module mld_z_sludist_solver
use mld_z_base_solver_mod
#if defined(LPK8)
type, extends(mld_z_base_solver_type) :: mld_z_sludist_solver_type
end type mld_z_sludist_solver_type

@ -102,14 +102,14 @@ module mld_z_symdec_aggregator_mod
interface
subroutine mld_z_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info)
import :: mld_z_symdec_aggregator_type, psb_desc_type, psb_zspmat_type, psb_dpk_, &
& psb_ipk_, psb_epk_, mld_dml_parms
& psb_ipk_, psb_lpk_, psb_lzspmat_type, mld_dml_parms
implicit none
class(mld_z_symdec_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_lpk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:)
type(psb_lzspmat_type), intent(out) :: op_prol
integer(psb_ipk_), intent(out) :: info
end subroutine mld_z_symdec_aggregator_build_tprol
end interface

Loading…
Cancel
Save