|
|
@ -36,7 +36,7 @@
|
|
|
|
!
|
|
|
|
!
|
|
|
|
!
|
|
|
|
!
|
|
|
|
subroutine mld_d_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,&
|
|
|
|
subroutine mld_d_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,&
|
|
|
|
& coo_prol,desc_cprol,coo_restr,info)
|
|
|
|
& coo_prol,desc_ac,coo_restr,info)
|
|
|
|
use psb_base_mod
|
|
|
|
use psb_base_mod
|
|
|
|
use mld_d_inner_mod
|
|
|
|
use mld_d_inner_mod
|
|
|
|
use mld_d_base_aggregator_mod, mld_protect_name => mld_d_spmm_bld_inner
|
|
|
|
use mld_d_base_aggregator_mod, mld_protect_name => mld_d_spmm_bld_inner
|
|
|
@ -48,7 +48,7 @@ subroutine mld_d_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,&
|
|
|
|
integer(psb_lpk_), intent(inout) :: nlaggr(:)
|
|
|
|
integer(psb_lpk_), intent(inout) :: nlaggr(:)
|
|
|
|
type(mld_dml_parms), intent(inout) :: parms
|
|
|
|
type(mld_dml_parms), intent(inout) :: parms
|
|
|
|
type(psb_ld_coo_sparse_mat), intent(inout) :: coo_prol, coo_restr
|
|
|
|
type(psb_ld_coo_sparse_mat), intent(inout) :: coo_prol, coo_restr
|
|
|
|
type(psb_desc_type), intent(inout) :: desc_cprol
|
|
|
|
type(psb_desc_type), intent(inout) :: desc_ac
|
|
|
|
type(psb_ldspmat_type), intent(out) :: ac
|
|
|
|
type(psb_ldspmat_type), intent(out) :: ac
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
|
|
|
|
|
|
|
@ -60,7 +60,7 @@ subroutine mld_d_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,&
|
|
|
|
type(psb_ld_coo_sparse_mat) :: ac_coo, tmpcoo
|
|
|
|
type(psb_ld_coo_sparse_mat) :: ac_coo, tmpcoo
|
|
|
|
type(psb_d_csr_sparse_mat) :: acsr3, csr_prol, ac_csr, csr_restr
|
|
|
|
type(psb_d_csr_sparse_mat) :: acsr3, csr_prol, ac_csr, csr_restr
|
|
|
|
integer(psb_ipk_) :: debug_level, debug_unit, naggr
|
|
|
|
integer(psb_ipk_) :: debug_level, debug_unit, naggr
|
|
|
|
integer(psb_lpk_) :: nrow, nglob, ncol, ntaggr, nzl, ip, &
|
|
|
|
integer(psb_lpk_) :: nrow, nglob, ncol, ntaggr, nrl, nzl, ip, &
|
|
|
|
& nzt, naggrm1, naggrp1, i, k
|
|
|
|
& nzt, naggrm1, naggrp1, i, k
|
|
|
|
integer(psb_lpk_) :: nrsave, ncsave, nzsave, nza
|
|
|
|
integer(psb_lpk_) :: nrsave, ncsave, nzsave, nza
|
|
|
|
logical, parameter :: do_timings=.false., oldstyle=.false., debug=.false.
|
|
|
|
logical, parameter :: do_timings=.false., oldstyle=.false., debug=.false.
|
|
|
@ -90,114 +90,210 @@ subroutine mld_d_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,&
|
|
|
|
naggrp1 = sum(nlaggr(1:me+1))
|
|
|
|
naggrp1 = sum(nlaggr(1:me+1))
|
|
|
|
!write(0,*)me,' ',name,' input sizes',nlaggr(:),':',naggr
|
|
|
|
!write(0,*)me,' ',name,' input sizes',nlaggr(:),':',naggr
|
|
|
|
|
|
|
|
|
|
|
|
!
|
|
|
|
if (.false.) then
|
|
|
|
! COO_PROL should arrive here with local numbering
|
|
|
|
!
|
|
|
|
!
|
|
|
|
! COO_PROL should arrive here with local numbering
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' Size check on entry New: ',&
|
|
|
|
!
|
|
|
|
& coo_prol%get_fmt(),coo_prol%get_nrows(),coo_prol%get_ncols(),coo_prol%get_nzeros(),&
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' Size check on entry New: ',&
|
|
|
|
& nrow,ntaggr,naggr
|
|
|
|
& coo_prol%get_fmt(),coo_prol%get_nrows(),coo_prol%get_ncols(),coo_prol%get_nzeros(),&
|
|
|
|
|
|
|
|
& nrow,ntaggr,naggr
|
|
|
|
call coo_prol%cp_to_ifmt(csr_prol,info)
|
|
|
|
|
|
|
|
|
|
|
|
call coo_prol%cp_to_ifmt(csr_prol,info)
|
|
|
|
if (debug) write(0,*) me,trim(name),' Product AxPROL ',&
|
|
|
|
|
|
|
|
& a_csr%get_nrows(),a_csr%get_ncols(), csr_prol%get_nrows(), &
|
|
|
|
if (debug) write(0,*) me,trim(name),' Product AxPROL ',&
|
|
|
|
& desc_a%get_local_rows(),desc_a%get_local_cols(),&
|
|
|
|
& a_csr%get_nrows(),a_csr%get_ncols(), csr_prol%get_nrows(), &
|
|
|
|
& desc_cprol%get_local_rows(),desc_a%get_local_cols()
|
|
|
|
& desc_a%get_local_rows(),desc_a%get_local_cols(),&
|
|
|
|
if (debug) flush(0)
|
|
|
|
& desc_ac%get_local_rows(),desc_a%get_local_cols()
|
|
|
|
|
|
|
|
if (debug) flush(0)
|
|
|
|
if (do_timings) call psb_tic(idx_spspmm)
|
|
|
|
|
|
|
|
call psb_par_spspmm(a_csr,desc_a,csr_prol,acsr3,desc_cprol,info)
|
|
|
|
if (do_timings) call psb_tic(idx_spspmm)
|
|
|
|
if (do_timings) call psb_toc(idx_spspmm)
|
|
|
|
call psb_par_spspmm(a_csr,desc_a,csr_prol,acsr3,desc_ac,info)
|
|
|
|
|
|
|
|
if (do_timings) call psb_toc(idx_spspmm)
|
|
|
|
if (debug) write(0,*) me,trim(name),' Done AxPROL ',&
|
|
|
|
|
|
|
|
& acsr3%get_nrows(),acsr3%get_ncols(), acsr3%get_nzeros(),&
|
|
|
|
if (debug) write(0,*) me,trim(name),' Done AxPROL ',&
|
|
|
|
& desc_cprol%get_local_rows(),desc_cprol%get_local_cols()
|
|
|
|
& acsr3%get_nrows(),acsr3%get_ncols(), acsr3%get_nzeros(),&
|
|
|
|
|
|
|
|
& desc_ac%get_local_rows(),desc_ac%get_local_cols()
|
|
|
|
!
|
|
|
|
|
|
|
|
! Ok first product done.
|
|
|
|
!
|
|
|
|
!
|
|
|
|
! Ok first product done.
|
|
|
|
! Remember that RESTR must be built from PROL after halo extension,
|
|
|
|
!
|
|
|
|
! which is done above in psb_par_spspmm
|
|
|
|
! Remember that RESTR must be built from PROL after halo extension,
|
|
|
|
if (debug) write(0,*)me,' ',name,' No inp_restr, transposing prol ',&
|
|
|
|
! which is done above in psb_par_spspmm
|
|
|
|
& csr_prol%get_nrows(),csr_prol%get_ncols(),csr_prol%get_nzeros()
|
|
|
|
if (debug) write(0,*)me,' ',name,' No inp_restr, transposing prol ',&
|
|
|
|
call csr_prol%cp_to_lcoo(coo_restr,info)
|
|
|
|
& csr_prol%get_nrows(),csr_prol%get_ncols(),csr_prol%get_nzeros()
|
|
|
|
|
|
|
|
call csr_prol%cp_to_lcoo(coo_restr,info)
|
|
|
|
!!$ write(0,*)me,' ',name,' new into transposition ',coo_restr%get_nrows(),&
|
|
|
|
!!$ write(0,*)me,' ',name,' new into transposition ',coo_restr%get_nrows(),&
|
|
|
|
!!$ & coo_restr%get_ncols(),coo_restr%get_nzeros()
|
|
|
|
!!$ & coo_restr%get_ncols(),coo_restr%get_nzeros()
|
|
|
|
call coo_restr%transp()
|
|
|
|
call coo_restr%transp()
|
|
|
|
nzl = coo_restr%get_nzeros()
|
|
|
|
nzl = coo_restr%get_nzeros()
|
|
|
|
call desc_cprol%l2gip(coo_restr%ia(1:nzl),info)
|
|
|
|
call desc_ac%l2gip(coo_restr%ia(1:nzl),info)
|
|
|
|
i=0
|
|
|
|
i=0
|
|
|
|
!
|
|
|
|
!
|
|
|
|
! Now we have to fix this. The only rows of the restrictor that are correct
|
|
|
|
! Now we have to fix this. The only rows of the restrictor that are correct
|
|
|
|
! are those corresponding to "local" aggregates, i.e. indices in ilaggr(:)
|
|
|
|
! are those corresponding to "local" aggregates, i.e. indices in ilaggr(:)
|
|
|
|
!
|
|
|
|
!
|
|
|
|
do k=1, nzl
|
|
|
|
do k=1, nzl
|
|
|
|
if ((naggrm1 < coo_restr%ia(k)) .and.(coo_restr%ia(k) <= naggrp1)) then
|
|
|
|
if ((naggrm1 < coo_restr%ia(k)) .and.(coo_restr%ia(k) <= naggrp1)) then
|
|
|
|
i = i+1
|
|
|
|
i = i+1
|
|
|
|
coo_restr%val(i) = coo_restr%val(k)
|
|
|
|
coo_restr%val(i) = coo_restr%val(k)
|
|
|
|
coo_restr%ia(i) = coo_restr%ia(k)
|
|
|
|
coo_restr%ia(i) = coo_restr%ia(k)
|
|
|
|
coo_restr%ja(i) = coo_restr%ja(k)
|
|
|
|
coo_restr%ja(i) = coo_restr%ja(k)
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
call coo_restr%set_nzeros(i)
|
|
|
|
call coo_restr%set_nzeros(i)
|
|
|
|
call coo_restr%fix(info)
|
|
|
|
call coo_restr%fix(info)
|
|
|
|
call coo_restr%cp_to_coo(tmpcoo,info)
|
|
|
|
call coo_restr%cp_to_coo(tmpcoo,info)
|
|
|
|
!!$ write(0,*)me,' ',name,' after transposition ',coo_restr%get_nrows(),coo_restr%get_ncols(),coo_restr%get_nzeros()
|
|
|
|
!!$ write(0,*)me,' ',name,' after transposition ',coo_restr%get_nrows(),coo_restr%get_ncols(),coo_restr%get_nzeros()
|
|
|
|
|
|
|
|
|
|
|
|
if (info /= psb_success_) then
|
|
|
|
if (info /= psb_success_) then
|
|
|
|
call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv coo_restr')
|
|
|
|
call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv coo_restr')
|
|
|
|
goto 9999
|
|
|
|
goto 9999
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
if (debug_level >= psb_debug_outer_) &
|
|
|
|
if (debug_level >= psb_debug_outer_) &
|
|
|
|
& write(debug_unit,*) me,' ',trim(name),&
|
|
|
|
& write(debug_unit,*) me,' ',trim(name),&
|
|
|
|
& 'starting sphalo/ rwxtd'
|
|
|
|
& 'starting sphalo/ rwxtd'
|
|
|
|
nzl = tmpcoo%get_nzeros()
|
|
|
|
nzl = tmpcoo%get_nzeros()
|
|
|
|
call psb_glob_to_loc(tmpcoo%ia(1:nzl),desc_cprol,info,iact='I',owned=.true.)
|
|
|
|
call psb_glob_to_loc(tmpcoo%ia(1:nzl),desc_ac,info,iact='I',owned=.true.)
|
|
|
|
call tmpcoo%clean_negidx(info)
|
|
|
|
call tmpcoo%clean_negidx(info)
|
|
|
|
nzl = tmpcoo%get_nzeros()
|
|
|
|
nzl = tmpcoo%get_nzeros()
|
|
|
|
call tmpcoo%set_nrows(desc_cprol%get_local_rows())
|
|
|
|
call tmpcoo%set_nrows(desc_ac%get_local_rows())
|
|
|
|
call tmpcoo%set_ncols(desc_a%get_local_cols())
|
|
|
|
call tmpcoo%set_ncols(desc_a%get_local_cols())
|
|
|
|
!!$ write(0,*)me,' ',name,' after G2L on rows ',tmpcoo%get_nrows(),tmpcoo%get_ncols(),tmpcoo%get_nzeros()
|
|
|
|
!!$ write(0,*)me,' ',name,' after G2L on rows ',tmpcoo%get_nrows(),tmpcoo%get_ncols(),tmpcoo%get_nzeros()
|
|
|
|
call csr_restr%mv_from_lcoo(tmpcoo,info)
|
|
|
|
call csr_restr%mv_from_lcoo(tmpcoo,info)
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,trim(name),' Product RESTRxAP ',&
|
|
|
|
if (debug) write(0,*) me,trim(name),' Product RESTRxAP ',&
|
|
|
|
& csr_restr%get_nrows(),csr_restr%get_ncols(), &
|
|
|
|
& csr_restr%get_nrows(),csr_restr%get_ncols(), &
|
|
|
|
& desc_cprol%get_local_rows(),desc_a%get_local_cols(),&
|
|
|
|
& desc_ac%get_local_rows(),desc_a%get_local_cols(),&
|
|
|
|
& acsr3%get_nrows(),acsr3%get_ncols()
|
|
|
|
& acsr3%get_nrows(),acsr3%get_ncols()
|
|
|
|
if (do_timings) call psb_tic(idx_spspmm)
|
|
|
|
if (do_timings) call psb_tic(idx_spspmm)
|
|
|
|
call psb_par_spspmm(csr_restr,desc_a,acsr3,ac_csr,desc_cprol,info)
|
|
|
|
call psb_par_spspmm(csr_restr,desc_a,acsr3,ac_csr,desc_ac,info)
|
|
|
|
if (do_timings) call psb_toc(idx_spspmm)
|
|
|
|
if (do_timings) call psb_toc(idx_spspmm)
|
|
|
|
call csr_restr%free()
|
|
|
|
call csr_restr%free()
|
|
|
|
call acsr3%free()
|
|
|
|
call acsr3%free()
|
|
|
|
call ac_csr%mv_to_lcoo(ac_coo,info)
|
|
|
|
call ac_csr%mv_to_lcoo(ac_coo,info)
|
|
|
|
call ac_coo%fix(info)
|
|
|
|
call ac_coo%fix(info)
|
|
|
|
nza = ac_coo%get_nzeros()
|
|
|
|
nza = ac_coo%get_nzeros()
|
|
|
|
if (debug) write(0,*) me,trim(name),' Fixed ac ',&
|
|
|
|
if (debug) write(0,*) me,trim(name),' Fixed ac ',&
|
|
|
|
& ac_coo%get_nrows(),ac_coo%get_ncols(), nza
|
|
|
|
& ac_coo%get_nrows(),ac_coo%get_ncols(), nza
|
|
|
|
call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info)
|
|
|
|
call desc_ac%indxmap%l2gip(ac_coo%ia(1:nza),info)
|
|
|
|
call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info)
|
|
|
|
call desc_ac%indxmap%l2gip(ac_coo%ja(1:nza),info)
|
|
|
|
call ac_coo%set_nrows(ntaggr)
|
|
|
|
call ac_coo%set_nrows(ntaggr)
|
|
|
|
call ac_coo%set_ncols(ntaggr)
|
|
|
|
call ac_coo%set_ncols(ntaggr)
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' Before mv_from',psb_get_errstatus()
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' Before mv_from',psb_get_errstatus()
|
|
|
|
if (info == 0) call ac%mv_from(ac_coo)
|
|
|
|
if (info == 0) call ac%mv_from(ac_coo)
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' After mv_from',psb_get_errstatus()
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' After mv_from',psb_get_errstatus()
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' ',ac%get_fmt(),ac%get_nrows(),ac%get_ncols(),ac%get_nzeros(),naggr,ntaggr
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' ',ac%get_fmt(),ac%get_nrows(),ac%get_ncols(),ac%get_nzeros(),naggr,ntaggr
|
|
|
|
! write(0,*) me,' ',trim(name),' Final AC newstyle ',ac%get_fmt(),ac%get_nrows(),ac%get_ncols(),ac%get_nzeros()
|
|
|
|
! write(0,*) me,' ',trim(name),' Final AC newstyle ',ac%get_fmt(),ac%get_nrows(),ac%get_ncols(),ac%get_nzeros()
|
|
|
|
|
|
|
|
|
|
|
|
nza = coo_prol%get_nzeros()
|
|
|
|
nza = coo_prol%get_nzeros()
|
|
|
|
call desc_cprol%indxmap%l2gip(coo_prol%ja(1:nza),info)
|
|
|
|
call desc_ac%indxmap%l2gip(coo_prol%ja(1:nza),info)
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) then
|
|
|
|
if (debug) then
|
|
|
|
write(0,*) me,' ',trim(name),' Checkpoint at exit'
|
|
|
|
write(0,*) me,' ',trim(name),' Checkpoint at exit'
|
|
|
|
call psb_barrier(ictxt)
|
|
|
|
call psb_barrier(ictxt)
|
|
|
|
write(0,*) me,' ',trim(name),' Checkpoint through'
|
|
|
|
write(0,*) me,' ',trim(name),' Checkpoint through'
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
if (info /= psb_success_) then
|
|
|
|
if (info /= psb_success_) then
|
|
|
|
call psb_errpush(psb_err_internal_error_,name,a_err='Build ac = coo_restr x am3')
|
|
|
|
call psb_errpush(psb_err_internal_error_,name,a_err='Build ac = coo_restr x am3')
|
|
|
|
goto 9999
|
|
|
|
goto 9999
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
else
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
! COO_PROL should arrive here with local numbering
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' Size check on entry New: ',&
|
|
|
|
|
|
|
|
& coo_prol%get_fmt(),coo_prol%get_nrows(),coo_prol%get_ncols(),coo_prol%get_nzeros(),&
|
|
|
|
|
|
|
|
& nrow,ntaggr,naggr
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call coo_prol%cp_to_ifmt(csr_prol,info)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,trim(name),' Product AxPROL ',&
|
|
|
|
|
|
|
|
& a_csr%get_nrows(),a_csr%get_ncols(), csr_prol%get_nrows(), &
|
|
|
|
|
|
|
|
& desc_a%get_local_rows(),desc_a%get_local_cols(),&
|
|
|
|
|
|
|
|
& desc_ac%get_local_rows(),desc_a%get_local_cols()
|
|
|
|
|
|
|
|
if (debug) flush(0)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if (do_timings) call psb_tic(idx_spspmm)
|
|
|
|
|
|
|
|
call psb_par_spspmm(a_csr,desc_a,csr_prol,acsr3,desc_ac,info)
|
|
|
|
|
|
|
|
if (do_timings) call psb_toc(idx_spspmm)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,trim(name),' Done AxPROL ',&
|
|
|
|
|
|
|
|
& acsr3%get_nrows(),acsr3%get_ncols(), acsr3%get_nzeros(),&
|
|
|
|
|
|
|
|
& desc_ac%get_local_rows(),desc_ac%get_local_cols()
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
! Ok first product done.
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
! Remember that RESTR must be built from PROL after halo extension,
|
|
|
|
|
|
|
|
! which is done above in psb_par_spspmm
|
|
|
|
|
|
|
|
if (debug) write(0,*)me,' ',name,' No inp_restr, transposing prol ',&
|
|
|
|
|
|
|
|
& csr_prol%get_nrows(),csr_prol%get_ncols(),csr_prol%get_nzeros()
|
|
|
|
|
|
|
|
call csr_prol%mv_to_lcoo(coo_restr,info)
|
|
|
|
|
|
|
|
!!$ write(0,*)me,' ',name,' new into transposition ',coo_restr%get_nrows(),&
|
|
|
|
|
|
|
|
!!$ & coo_restr%get_ncols(),coo_restr%get_nzeros()
|
|
|
|
|
|
|
|
if (debug) call check_coo(me,trim(name)//' Check 1 (before transp) on coo_restr:',coo_restr)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call coo_restr%transp()
|
|
|
|
|
|
|
|
nzl = coo_restr%get_nzeros()
|
|
|
|
|
|
|
|
nrl = desc_ac%get_local_rows()
|
|
|
|
|
|
|
|
i=0
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
! Only keep local rows
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
do k=1, nzl
|
|
|
|
|
|
|
|
if ((1 <= coo_restr%ia(k)) .and.(coo_restr%ia(k) <= nrl)) then
|
|
|
|
|
|
|
|
i = i+1
|
|
|
|
|
|
|
|
coo_restr%val(i) = coo_restr%val(k)
|
|
|
|
|
|
|
|
coo_restr%ia(i) = coo_restr%ia(k)
|
|
|
|
|
|
|
|
coo_restr%ja(i) = coo_restr%ja(k)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
call coo_restr%set_nzeros(i)
|
|
|
|
|
|
|
|
call coo_restr%fix(info)
|
|
|
|
|
|
|
|
nzl = coo_restr%get_nzeros()
|
|
|
|
|
|
|
|
call coo_restr%set_nrows(desc_ac%get_local_rows())
|
|
|
|
|
|
|
|
call coo_restr%set_ncols(desc_a%get_local_cols())
|
|
|
|
|
|
|
|
if (debug) call check_coo(me,trim(name)//' Check 2 on coo_restr:',coo_restr)
|
|
|
|
|
|
|
|
call csr_restr%cp_from_lcoo(coo_restr,info)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
!!$ write(0,*)me,' ',name,' after transposition ',coo_restr%get_nrows(),coo_restr%get_ncols(),coo_restr%get_nzeros()
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if (info /= psb_success_) then
|
|
|
|
|
|
|
|
call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv coo_restr')
|
|
|
|
|
|
|
|
goto 9999
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
if (debug_level >= psb_debug_outer_) &
|
|
|
|
|
|
|
|
& write(debug_unit,*) me,' ',trim(name),&
|
|
|
|
|
|
|
|
& 'starting sphalo/ rwxtd'
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,trim(name),' Product RESTRxAP ',&
|
|
|
|
|
|
|
|
& csr_restr%get_nrows(),csr_restr%get_ncols(), &
|
|
|
|
|
|
|
|
& desc_ac%get_local_rows(),desc_a%get_local_cols(),&
|
|
|
|
|
|
|
|
& acsr3%get_nrows(),acsr3%get_ncols()
|
|
|
|
|
|
|
|
if (do_timings) call psb_tic(idx_spspmm)
|
|
|
|
|
|
|
|
call psb_par_spspmm(csr_restr,desc_a,acsr3,ac_csr,desc_ac,info)
|
|
|
|
|
|
|
|
if (do_timings) call psb_toc(idx_spspmm)
|
|
|
|
|
|
|
|
call acsr3%free()
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call psb_cdasb(desc_ac,info)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call ac_csr%set_nrows(desc_ac%get_local_rows())
|
|
|
|
|
|
|
|
call ac_csr%set_ncols(desc_ac%get_local_cols())
|
|
|
|
|
|
|
|
call ac%mv_from(ac_csr)
|
|
|
|
|
|
|
|
call ac%set_asb()
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' After mv_from',psb_get_errstatus()
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' ',ac%get_fmt(),ac%get_nrows(),ac%get_ncols(),ac%get_nzeros(),naggr,ntaggr
|
|
|
|
|
|
|
|
! write(0,*) me,' ',trim(name),' Final AC newstyle ',ac%get_fmt(),ac%get_nrows(),ac%get_ncols(),ac%get_nzeros()
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call coo_prol%set_ncols(desc_ac%get_local_cols())
|
|
|
|
|
|
|
|
!call coo_restr%mv_from_ifmt(csr_restr,info)
|
|
|
|
|
|
|
|
!!$ call coo_restr%set_nrows(desc_ac%get_local_rows())
|
|
|
|
|
|
|
|
!!$ call coo_restr%set_ncols(desc_a%get_local_cols())
|
|
|
|
|
|
|
|
if (debug) call check_coo(me,trim(name)//' Check 3 on coo_restr:',coo_restr)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
if (debug_level >= psb_debug_outer_) &
|
|
|
|
if (debug_level >= psb_debug_outer_) &
|
|
|
|
& write(debug_unit,*) me,' ',trim(name),&
|
|
|
|
& write(debug_unit,*) me,' ',trim(name),&
|
|
|
@ -209,11 +305,26 @@ subroutine mld_d_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,&
|
|
|
|
9999 call psb_error_handler(err_act)
|
|
|
|
9999 call psb_error_handler(err_act)
|
|
|
|
|
|
|
|
|
|
|
|
return
|
|
|
|
return
|
|
|
|
|
|
|
|
contains
|
|
|
|
|
|
|
|
subroutine check_coo(me,string,coo)
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
integer(psb_ipk_) :: me
|
|
|
|
|
|
|
|
type(psb_ld_coo_sparse_mat) :: coo
|
|
|
|
|
|
|
|
character(len=*) :: string
|
|
|
|
|
|
|
|
integer(psb_lpk_) :: nr,nc,nz
|
|
|
|
|
|
|
|
nr = coo%get_nrows()
|
|
|
|
|
|
|
|
nc = coo%get_ncols()
|
|
|
|
|
|
|
|
nz = coo%get_nzeros()
|
|
|
|
|
|
|
|
write(0,*) me,string,nr,nc,&
|
|
|
|
|
|
|
|
& minval(coo%ia(1:nz)),maxval(coo%ia(1:nz)),&
|
|
|
|
|
|
|
|
& minval(coo%ja(1:nz)),maxval(coo%ja(1:nz))
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
end subroutine check_coo
|
|
|
|
|
|
|
|
|
|
|
|
end subroutine mld_d_spmm_bld_inner
|
|
|
|
end subroutine mld_d_spmm_bld_inner
|
|
|
|
|
|
|
|
|
|
|
|
subroutine mld_ld_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,&
|
|
|
|
subroutine mld_ld_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,&
|
|
|
|
& coo_prol,desc_cprol,coo_restr,info)
|
|
|
|
& coo_prol,desc_ac,coo_restr,info)
|
|
|
|
use psb_base_mod
|
|
|
|
use psb_base_mod
|
|
|
|
use mld_d_inner_mod
|
|
|
|
use mld_d_inner_mod
|
|
|
|
use mld_d_base_aggregator_mod, mld_protect_name => mld_ld_spmm_bld_inner
|
|
|
|
use mld_d_base_aggregator_mod, mld_protect_name => mld_ld_spmm_bld_inner
|
|
|
@ -225,7 +336,7 @@ subroutine mld_ld_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,&
|
|
|
|
integer(psb_lpk_), intent(inout) :: nlaggr(:)
|
|
|
|
integer(psb_lpk_), intent(inout) :: nlaggr(:)
|
|
|
|
type(mld_dml_parms), intent(inout) :: parms
|
|
|
|
type(mld_dml_parms), intent(inout) :: parms
|
|
|
|
type(psb_ld_coo_sparse_mat), intent(inout) :: coo_prol, coo_restr
|
|
|
|
type(psb_ld_coo_sparse_mat), intent(inout) :: coo_prol, coo_restr
|
|
|
|
type(psb_desc_type), intent(inout) :: desc_cprol
|
|
|
|
type(psb_desc_type), intent(inout) :: desc_ac
|
|
|
|
type(psb_ldspmat_type), intent(out) :: ac
|
|
|
|
type(psb_ldspmat_type), intent(out) :: ac
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
|
|
|
|
|
|
|
@ -237,7 +348,7 @@ subroutine mld_ld_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,&
|
|
|
|
type(psb_ld_coo_sparse_mat) :: ac_coo, tmpcoo
|
|
|
|
type(psb_ld_coo_sparse_mat) :: ac_coo, tmpcoo
|
|
|
|
type(psb_ld_csr_sparse_mat) :: acsr3, csr_prol, ac_csr, csr_restr
|
|
|
|
type(psb_ld_csr_sparse_mat) :: acsr3, csr_prol, ac_csr, csr_restr
|
|
|
|
integer(psb_ipk_) :: debug_level, debug_unit, naggr
|
|
|
|
integer(psb_ipk_) :: debug_level, debug_unit, naggr
|
|
|
|
integer(psb_lpk_) :: nrow, nglob, ncol, ntaggr, nzl, ip, &
|
|
|
|
integer(psb_lpk_) :: nrow, nglob, ncol, ntaggr, nrl, nzl, ip, &
|
|
|
|
& nzt, naggrm1, naggrp1, i, k
|
|
|
|
& nzt, naggrm1, naggrp1, i, k
|
|
|
|
integer(psb_lpk_) :: nrsave, ncsave, nzsave, nza
|
|
|
|
integer(psb_lpk_) :: nrsave, ncsave, nzsave, nza
|
|
|
|
logical, parameter :: do_timings=.true., oldstyle=.false., debug=.false.
|
|
|
|
logical, parameter :: do_timings=.true., oldstyle=.false., debug=.false.
|
|
|
@ -266,113 +377,208 @@ subroutine mld_ld_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,&
|
|
|
|
naggrm1 = sum(nlaggr(1:me))
|
|
|
|
naggrm1 = sum(nlaggr(1:me))
|
|
|
|
naggrp1 = sum(nlaggr(1:me+1))
|
|
|
|
naggrp1 = sum(nlaggr(1:me+1))
|
|
|
|
!write(0,*)me,' ',name,' input sizes',nlaggr(:),':',naggr
|
|
|
|
!write(0,*)me,' ',name,' input sizes',nlaggr(:),':',naggr
|
|
|
|
|
|
|
|
if (.false.) then
|
|
|
|
!
|
|
|
|
!
|
|
|
|
! Here COO_PROL should be with GLOBAL indices on the cols
|
|
|
|
! Here COO_PROL should be with GLOBAL indices on the cols
|
|
|
|
! and LOCAL indices on the rows.
|
|
|
|
! and LOCAL indices on the rows.
|
|
|
|
!
|
|
|
|
!
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' Size check on entry New: ',&
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' Size check on entry New: ',&
|
|
|
|
& coo_prol%get_fmt(),coo_prol%get_nrows(),coo_prol%get_ncols(),coo_prol%get_nzeros(),&
|
|
|
|
& coo_prol%get_fmt(),coo_prol%get_nrows(),coo_prol%get_ncols(),coo_prol%get_nzeros(),&
|
|
|
|
& nrow,ntaggr,naggr
|
|
|
|
& nrow,ntaggr,naggr
|
|
|
|
|
|
|
|
|
|
|
|
call coo_prol%cp_to_fmt(csr_prol,info)
|
|
|
|
call coo_prol%cp_to_fmt(csr_prol,info)
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,trim(name),' Product AxPROL ',&
|
|
|
|
if (debug) write(0,*) me,trim(name),' Product AxPROL ',&
|
|
|
|
& a_csr%get_nrows(),a_csr%get_ncols(), csr_prol%get_nrows(), &
|
|
|
|
& a_csr%get_nrows(),a_csr%get_ncols(), csr_prol%get_nrows(), &
|
|
|
|
& desc_a%get_local_rows(),desc_a%get_local_cols(),&
|
|
|
|
& desc_a%get_local_rows(),desc_a%get_local_cols(),&
|
|
|
|
& desc_cprol%get_local_rows(),desc_a%get_local_cols()
|
|
|
|
& desc_ac%get_local_rows(),desc_a%get_local_cols()
|
|
|
|
if (debug) flush(0)
|
|
|
|
if (debug) flush(0)
|
|
|
|
|
|
|
|
|
|
|
|
if (do_timings) call psb_tic(idx_spspmm)
|
|
|
|
if (do_timings) call psb_tic(idx_spspmm)
|
|
|
|
call psb_par_spspmm(a_csr,desc_a,csr_prol,acsr3,desc_cprol,info)
|
|
|
|
call psb_par_spspmm(a_csr,desc_a,csr_prol,acsr3,desc_ac,info)
|
|
|
|
if (do_timings) call psb_toc(idx_spspmm)
|
|
|
|
if (do_timings) call psb_toc(idx_spspmm)
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,trim(name),' Done AxPROL ',&
|
|
|
|
if (debug) write(0,*) me,trim(name),' Done AxPROL ',&
|
|
|
|
& acsr3%get_nrows(),acsr3%get_ncols(), acsr3%get_nzeros(),&
|
|
|
|
& acsr3%get_nrows(),acsr3%get_ncols(), acsr3%get_nzeros(),&
|
|
|
|
& desc_cprol%get_local_rows(),desc_cprol%get_local_cols()
|
|
|
|
& desc_ac%get_local_rows(),desc_ac%get_local_cols()
|
|
|
|
|
|
|
|
|
|
|
|
!
|
|
|
|
!
|
|
|
|
! Ok first product done.
|
|
|
|
! Ok first product done.
|
|
|
|
!
|
|
|
|
!
|
|
|
|
! Remember that RESTR must be built from PROL after halo extension,
|
|
|
|
! Remember that RESTR must be built from PROL after halo extension,
|
|
|
|
! which is done above in psb_par_spspmm
|
|
|
|
! which is done above in psb_par_spspmm
|
|
|
|
if (debug) write(0,*)me,' ',name,' No inp_restr, transposing prol ',&
|
|
|
|
if (debug) write(0,*)me,' ',name,' No inp_restr, transposing prol ',&
|
|
|
|
& csr_prol%get_nrows(),csr_prol%get_ncols(),csr_prol%get_nzeros()
|
|
|
|
& csr_prol%get_nrows(),csr_prol%get_ncols(),csr_prol%get_nzeros()
|
|
|
|
call csr_prol%cp_to_fmt(coo_restr,info)
|
|
|
|
call csr_prol%cp_to_fmt(coo_restr,info)
|
|
|
|
!!$ write(0,*)me,' ',name,' new into transposition ',coo_restr%get_nrows(),&
|
|
|
|
!!$ write(0,*)me,' ',name,' new into transposition ',coo_restr%get_nrows(),&
|
|
|
|
!!$ & coo_restr%get_ncols(),coo_restr%get_nzeros()
|
|
|
|
!!$ & coo_restr%get_ncols(),coo_restr%get_nzeros()
|
|
|
|
call coo_restr%transp()
|
|
|
|
call coo_restr%transp()
|
|
|
|
nzl = coo_restr%get_nzeros()
|
|
|
|
nzl = coo_restr%get_nzeros()
|
|
|
|
call desc_cprol%l2gip(coo_restr%ia(1:nzl),info)
|
|
|
|
call desc_ac%l2gip(coo_restr%ia(1:nzl),info)
|
|
|
|
i=0
|
|
|
|
i=0
|
|
|
|
!
|
|
|
|
!
|
|
|
|
! Now we have to fix this. The only rows of the restrictor that are correct
|
|
|
|
! Now we have to fix this. The only rows of the restrictor that are correct
|
|
|
|
! are those corresponding to "local" aggregates, i.e. indices in ilaggr(:)
|
|
|
|
! are those corresponding to "local" aggregates, i.e. indices in ilaggr(:)
|
|
|
|
!
|
|
|
|
!
|
|
|
|
do k=1, nzl
|
|
|
|
do k=1, nzl
|
|
|
|
if ((naggrm1 < coo_restr%ia(k)) .and.(coo_restr%ia(k) <= naggrp1)) then
|
|
|
|
if ((naggrm1 < coo_restr%ia(k)) .and.(coo_restr%ia(k) <= naggrp1)) then
|
|
|
|
i = i+1
|
|
|
|
i = i+1
|
|
|
|
coo_restr%val(i) = coo_restr%val(k)
|
|
|
|
coo_restr%val(i) = coo_restr%val(k)
|
|
|
|
coo_restr%ia(i) = coo_restr%ia(k)
|
|
|
|
coo_restr%ia(i) = coo_restr%ia(k)
|
|
|
|
coo_restr%ja(i) = coo_restr%ja(k)
|
|
|
|
coo_restr%ja(i) = coo_restr%ja(k)
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
call coo_restr%set_nzeros(i)
|
|
|
|
call coo_restr%set_nzeros(i)
|
|
|
|
call coo_restr%fix(info)
|
|
|
|
call coo_restr%fix(info)
|
|
|
|
call coo_restr%cp_to_coo(tmpcoo,info)
|
|
|
|
call coo_restr%cp_to_coo(tmpcoo,info)
|
|
|
|
!!$ write(0,*)me,' ',name,' after transposition ',coo_restr%get_nrows(),coo_restr%get_ncols(),coo_restr%get_nzeros()
|
|
|
|
!!$ write(0,*)me,' ',name,' after transposition ',coo_restr%get_nrows(),coo_restr%get_ncols(),coo_restr%get_nzeros()
|
|
|
|
|
|
|
|
|
|
|
|
if (info /= psb_success_) then
|
|
|
|
if (info /= psb_success_) then
|
|
|
|
call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv coo_restr')
|
|
|
|
call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv coo_restr')
|
|
|
|
goto 9999
|
|
|
|
goto 9999
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
if (debug_level >= psb_debug_outer_) &
|
|
|
|
if (debug_level >= psb_debug_outer_) &
|
|
|
|
& write(debug_unit,*) me,' ',trim(name),&
|
|
|
|
& write(debug_unit,*) me,' ',trim(name),&
|
|
|
|
& 'starting sphalo/ rwxtd'
|
|
|
|
& 'starting sphalo/ rwxtd'
|
|
|
|
nzl = tmpcoo%get_nzeros()
|
|
|
|
nzl = tmpcoo%get_nzeros()
|
|
|
|
call psb_glob_to_loc(tmpcoo%ia(1:nzl),desc_cprol,info,iact='I',owned=.true.)
|
|
|
|
call psb_glob_to_loc(tmpcoo%ia(1:nzl),desc_ac,info,iact='I',owned=.true.)
|
|
|
|
call tmpcoo%clean_negidx(info)
|
|
|
|
call tmpcoo%clean_negidx(info)
|
|
|
|
nzl = tmpcoo%get_nzeros()
|
|
|
|
nzl = tmpcoo%get_nzeros()
|
|
|
|
call tmpcoo%set_nrows(desc_cprol%get_local_rows())
|
|
|
|
call tmpcoo%set_nrows(desc_ac%get_local_rows())
|
|
|
|
call tmpcoo%set_ncols(desc_a%get_local_cols())
|
|
|
|
call tmpcoo%set_ncols(desc_a%get_local_cols())
|
|
|
|
!!$ write(0,*)me,' ',name,' after G2L on rows ',tmpcoo%get_nrows(),tmpcoo%get_ncols(),tmpcoo%get_nzeros()
|
|
|
|
!!$ write(0,*)me,' ',name,' after G2L on rows ',tmpcoo%get_nrows(),tmpcoo%get_ncols(),tmpcoo%get_nzeros()
|
|
|
|
call csr_restr%mv_from_coo(tmpcoo,info)
|
|
|
|
call csr_restr%mv_from_coo(tmpcoo,info)
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,trim(name),' Product RESTRxAP ',&
|
|
|
|
if (debug) write(0,*) me,trim(name),' Product RESTRxAP ',&
|
|
|
|
& csr_restr%get_nrows(),csr_restr%get_ncols(), &
|
|
|
|
& csr_restr%get_nrows(),csr_restr%get_ncols(), &
|
|
|
|
& desc_cprol%get_local_rows(),desc_a%get_local_cols(),&
|
|
|
|
& desc_ac%get_local_rows(),desc_a%get_local_cols(),&
|
|
|
|
& acsr3%get_nrows(),acsr3%get_ncols()
|
|
|
|
& acsr3%get_nrows(),acsr3%get_ncols()
|
|
|
|
if (do_timings) call psb_tic(idx_spspmm)
|
|
|
|
if (do_timings) call psb_tic(idx_spspmm)
|
|
|
|
call psb_par_spspmm(csr_restr,desc_a,acsr3,ac_csr,desc_cprol,info)
|
|
|
|
call psb_par_spspmm(csr_restr,desc_a,acsr3,ac_csr,desc_ac,info)
|
|
|
|
if (do_timings) call psb_toc(idx_spspmm)
|
|
|
|
if (do_timings) call psb_toc(idx_spspmm)
|
|
|
|
call csr_restr%free()
|
|
|
|
call csr_restr%free()
|
|
|
|
call ac_csr%mv_to_coo(ac_coo,info)
|
|
|
|
call ac_csr%mv_to_coo(ac_coo,info)
|
|
|
|
nza = ac_coo%get_nzeros()
|
|
|
|
nza = ac_coo%get_nzeros()
|
|
|
|
if (debug) write(0,*) me,trim(name),' Fixing ac ',&
|
|
|
|
if (debug) write(0,*) me,trim(name),' Fixing ac ',&
|
|
|
|
& ac_coo%get_nrows(),ac_coo%get_ncols(), nza
|
|
|
|
& ac_coo%get_nrows(),ac_coo%get_ncols(), nza
|
|
|
|
call ac_coo%fix(info)
|
|
|
|
call ac_coo%fix(info)
|
|
|
|
call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info)
|
|
|
|
call desc_ac%indxmap%l2gip(ac_coo%ia(1:nza),info)
|
|
|
|
call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info)
|
|
|
|
call desc_ac%indxmap%l2gip(ac_coo%ja(1:nza),info)
|
|
|
|
call ac_coo%set_nrows(ntaggr)
|
|
|
|
call ac_coo%set_nrows(ntaggr)
|
|
|
|
call ac_coo%set_ncols(ntaggr)
|
|
|
|
call ac_coo%set_ncols(ntaggr)
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' Before mv_from',psb_get_errstatus()
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' Before mv_from',psb_get_errstatus()
|
|
|
|
if (info == 0) call ac%mv_from(ac_coo)
|
|
|
|
if (info == 0) call ac%mv_from(ac_coo)
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' After mv_from',psb_get_errstatus()
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' After mv_from',psb_get_errstatus()
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' ',ac%get_fmt(),ac%get_nrows(),ac%get_ncols(),ac%get_nzeros(),naggr,ntaggr
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' ',ac%get_fmt(),ac%get_nrows(),ac%get_ncols(),ac%get_nzeros(),naggr,ntaggr
|
|
|
|
! write(0,*) me,' ',trim(name),' Final AC newstyle ',ac%get_fmt(),ac%get_nrows(),ac%get_ncols(),ac%get_nzeros()
|
|
|
|
! write(0,*) me,' ',trim(name),' Final AC newstyle ',ac%get_fmt(),ac%get_nrows(),ac%get_ncols(),ac%get_nzeros()
|
|
|
|
|
|
|
|
|
|
|
|
nza = coo_prol%get_nzeros()
|
|
|
|
nza = coo_prol%get_nzeros()
|
|
|
|
call desc_cprol%indxmap%l2gip(coo_prol%ja(1:nza),info)
|
|
|
|
call desc_ac%indxmap%l2gip(coo_prol%ja(1:nza),info)
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) then
|
|
|
|
if (debug) then
|
|
|
|
write(0,*) me,' ',trim(name),' Checkpoint at exit'
|
|
|
|
write(0,*) me,' ',trim(name),' Checkpoint at exit'
|
|
|
|
call psb_barrier(ictxt)
|
|
|
|
call psb_barrier(ictxt)
|
|
|
|
write(0,*) me,' ',trim(name),' Checkpoint through'
|
|
|
|
write(0,*) me,' ',trim(name),' Checkpoint through'
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
if (info /= psb_success_) then
|
|
|
|
if (info /= psb_success_) then
|
|
|
|
call psb_errpush(psb_err_internal_error_,name,a_err='Build ac = coo_restr x am3')
|
|
|
|
call psb_errpush(psb_err_internal_error_,name,a_err='Build ac = coo_restr x am3')
|
|
|
|
goto 9999
|
|
|
|
goto 9999
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
else
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
! COO_PROL should arrive here with local numbering
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' Size check on entry New: ',&
|
|
|
|
|
|
|
|
& coo_prol%get_fmt(),coo_prol%get_nrows(),coo_prol%get_ncols(),coo_prol%get_nzeros(),&
|
|
|
|
|
|
|
|
& nrow,ntaggr,naggr
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call coo_prol%cp_to_fmt(csr_prol,info)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,trim(name),' Product AxPROL ',&
|
|
|
|
|
|
|
|
& a_csr%get_nrows(),a_csr%get_ncols(), csr_prol%get_nrows(), &
|
|
|
|
|
|
|
|
& desc_a%get_local_rows(),desc_a%get_local_cols(),&
|
|
|
|
|
|
|
|
& desc_ac%get_local_rows(),desc_a%get_local_cols()
|
|
|
|
|
|
|
|
if (debug) flush(0)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if (do_timings) call psb_tic(idx_spspmm)
|
|
|
|
|
|
|
|
call psb_par_spspmm(a_csr,desc_a,csr_prol,acsr3,desc_ac,info)
|
|
|
|
|
|
|
|
if (do_timings) call psb_toc(idx_spspmm)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,trim(name),' Done AxPROL ',&
|
|
|
|
|
|
|
|
& acsr3%get_nrows(),acsr3%get_ncols(), acsr3%get_nzeros(),&
|
|
|
|
|
|
|
|
& desc_ac%get_local_rows(),desc_ac%get_local_cols()
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
! Ok first product done.
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
! Remember that RESTR must be built from PROL after halo extension,
|
|
|
|
|
|
|
|
! which is done above in psb_par_spspmm
|
|
|
|
|
|
|
|
if (debug) write(0,*)me,' ',name,' No inp_restr, transposing prol ',&
|
|
|
|
|
|
|
|
& csr_prol%get_nrows(),csr_prol%get_ncols(),csr_prol%get_nzeros()
|
|
|
|
|
|
|
|
call csr_prol%mv_to_coo(coo_restr,info)
|
|
|
|
|
|
|
|
!!$ write(0,*)me,' ',name,' new into transposition ',coo_restr%get_nrows(),&
|
|
|
|
|
|
|
|
!!$ & coo_restr%get_ncols(),coo_restr%get_nzeros()
|
|
|
|
|
|
|
|
if (debug) call check_coo(me,trim(name)//' Check 1 (before transp) on coo_restr:',coo_restr)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call coo_restr%transp()
|
|
|
|
|
|
|
|
nzl = coo_restr%get_nzeros()
|
|
|
|
|
|
|
|
nrl = desc_ac%get_local_rows()
|
|
|
|
|
|
|
|
i=0
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
! Only keep local rows
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
do k=1, nzl
|
|
|
|
|
|
|
|
if ((1 <= coo_restr%ia(k)) .and.(coo_restr%ia(k) <= nrl)) then
|
|
|
|
|
|
|
|
i = i+1
|
|
|
|
|
|
|
|
coo_restr%val(i) = coo_restr%val(k)
|
|
|
|
|
|
|
|
coo_restr%ia(i) = coo_restr%ia(k)
|
|
|
|
|
|
|
|
coo_restr%ja(i) = coo_restr%ja(k)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
call coo_restr%set_nzeros(i)
|
|
|
|
|
|
|
|
call coo_restr%fix(info)
|
|
|
|
|
|
|
|
nzl = coo_restr%get_nzeros()
|
|
|
|
|
|
|
|
call coo_restr%set_nrows(desc_ac%get_local_rows())
|
|
|
|
|
|
|
|
call coo_restr%set_ncols(desc_a%get_local_cols())
|
|
|
|
|
|
|
|
if (debug) call check_coo(me,trim(name)//' Check 2 on coo_restr:',coo_restr)
|
|
|
|
|
|
|
|
call csr_restr%cp_from_coo(coo_restr,info)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
!!$ write(0,*)me,' ',name,' after transposition ',coo_restr%get_nrows(),coo_restr%get_ncols(),coo_restr%get_nzeros()
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if (info /= psb_success_) then
|
|
|
|
|
|
|
|
call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv coo_restr')
|
|
|
|
|
|
|
|
goto 9999
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
if (debug_level >= psb_debug_outer_) &
|
|
|
|
|
|
|
|
& write(debug_unit,*) me,' ',trim(name),&
|
|
|
|
|
|
|
|
& 'starting sphalo/ rwxtd'
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,trim(name),' Product RESTRxAP ',&
|
|
|
|
|
|
|
|
& csr_restr%get_nrows(),csr_restr%get_ncols(), &
|
|
|
|
|
|
|
|
& desc_ac%get_local_rows(),desc_a%get_local_cols(),&
|
|
|
|
|
|
|
|
& acsr3%get_nrows(),acsr3%get_ncols()
|
|
|
|
|
|
|
|
if (do_timings) call psb_tic(idx_spspmm)
|
|
|
|
|
|
|
|
call psb_par_spspmm(csr_restr,desc_a,acsr3,ac_csr,desc_ac,info)
|
|
|
|
|
|
|
|
if (do_timings) call psb_toc(idx_spspmm)
|
|
|
|
|
|
|
|
call acsr3%free()
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call psb_cdasb(desc_ac,info)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call ac_csr%set_nrows(desc_ac%get_local_rows())
|
|
|
|
|
|
|
|
call ac_csr%set_ncols(desc_ac%get_local_cols())
|
|
|
|
|
|
|
|
call ac%mv_from(ac_csr)
|
|
|
|
|
|
|
|
call ac%set_asb()
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' After mv_from',psb_get_errstatus()
|
|
|
|
|
|
|
|
if (debug) write(0,*) me,' ',trim(name),' ',ac%get_fmt(),ac%get_nrows(),ac%get_ncols(),ac%get_nzeros(),naggr,ntaggr
|
|
|
|
|
|
|
|
! write(0,*) me,' ',trim(name),' Final AC newstyle ',ac%get_fmt(),ac%get_nrows(),ac%get_ncols(),ac%get_nzeros()
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call coo_prol%set_ncols(desc_ac%get_local_cols())
|
|
|
|
|
|
|
|
!call coo_restr%mv_from_ifmt(csr_restr,info)
|
|
|
|
|
|
|
|
!!$ call coo_restr%set_nrows(desc_ac%get_local_rows())
|
|
|
|
|
|
|
|
!!$ call coo_restr%set_ncols(desc_a%get_local_cols())
|
|
|
|
|
|
|
|
if (debug) call check_coo(me,trim(name)//' Check 3 on coo_restr:',coo_restr)
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
@ -387,4 +593,20 @@ subroutine mld_ld_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,&
|
|
|
|
|
|
|
|
|
|
|
|
return
|
|
|
|
return
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
contains
|
|
|
|
|
|
|
|
subroutine check_coo(me,string,coo)
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
integer(psb_ipk_) :: me
|
|
|
|
|
|
|
|
type(psb_ld_coo_sparse_mat) :: coo
|
|
|
|
|
|
|
|
character(len=*) :: string
|
|
|
|
|
|
|
|
integer(psb_lpk_) :: nr,nc,nz
|
|
|
|
|
|
|
|
nr = coo%get_nrows()
|
|
|
|
|
|
|
|
nc = coo%get_ncols()
|
|
|
|
|
|
|
|
nz = coo%get_nzeros()
|
|
|
|
|
|
|
|
write(0,*) me,string,nr,nc,&
|
|
|
|
|
|
|
|
& minval(coo%ia(1:nz)),maxval(coo%ia(1:nz)),&
|
|
|
|
|
|
|
|
& minval(coo%ja(1:nz)),maxval(coo%ja(1:nz))
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
end subroutine check_coo
|
|
|
|
|
|
|
|
|
|
|
|
end subroutine mld_ld_spmm_bld_inner
|
|
|
|
end subroutine mld_ld_spmm_bld_inner
|
|
|
|