From 6aed8608ca3e63ded500360fc15500905a064a3b Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Mon, 13 Apr 2020 13:17:50 +0200 Subject: [PATCH 01/11] New version X_spmm_bld_inner --- .../impl/aggregator/mld_c_spmm_bld_inner.f90 | 179 +++++++++++++++++- .../impl/aggregator/mld_d_spmm_bld_inner.f90 | 179 +++++++++++++++++- .../impl/aggregator/mld_s_spmm_bld_inner.f90 | 179 +++++++++++++++++- .../impl/aggregator/mld_z_spmm_bld_inner.f90 | 179 +++++++++++++++++- mlprec/mld_c_base_aggregator_mod.f90 | 22 ++- mlprec/mld_d_base_aggregator_mod.f90 | 22 ++- mlprec/mld_s_base_aggregator_mod.f90 | 22 ++- mlprec/mld_z_base_aggregator_mod.f90 | 22 ++- 8 files changed, 788 insertions(+), 16 deletions(-) diff --git a/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 index eb2da61e..d06878de 100644 --- a/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 @@ -42,6 +42,183 @@ subroutine mld_c_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& use mld_c_base_aggregator_mod, mld_protect_name => mld_c_spmm_bld_inner implicit none + ! Arguments + type(psb_c_csr_sparse_mat), intent(inout) :: a_csr + type(psb_desc_type), intent(in) :: desc_a + integer(psb_lpk_), intent(inout) :: nlaggr(:) + type(mld_sml_parms), intent(inout) :: parms + type(psb_lc_coo_sparse_mat), intent(inout) :: coo_prol, coo_restr + type(psb_desc_type), intent(inout) :: desc_cprol + type(psb_lcspmat_type), intent(out) :: ac + integer(psb_ipk_), intent(out) :: info + + ! Local variables + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ictxt,np,me, icomm, ndx, minfo + character(len=40) :: name + integer(psb_ipk_) :: ierr(5) + type(psb_lc_coo_sparse_mat) :: ac_coo, tmpcoo + type(psb_c_csr_sparse_mat) :: acsr3, csr_prol, ac_csr, csr_restr + integer(psb_ipk_) :: debug_level, debug_unit, naggr + integer(psb_lpk_) :: nrow, nglob, ncol, ntaggr, nzl, ip, & + & nzt, naggrm1, naggrp1, i, k + integer(psb_lpk_) :: nrsave, ncsave, nzsave, nza + logical, parameter :: do_timings=.true., oldstyle=.false., debug=.false. + integer(psb_ipk_), save :: idx_spspmm=-1 + + name='mld_spmm_bld_inner' + if(psb_get_errstatus().ne.0) return + info=psb_success_ + call psb_erractionsave(err_act) + + + ictxt = desc_a%get_context() + icomm = desc_a%get_mpic() + call psb_info(ictxt, me, np) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + nglob = desc_a%get_global_rows() + nrow = desc_a%get_local_rows() + ncol = desc_a%get_local_cols() + + if ((do_timings).and.(idx_spspmm==-1)) & + & idx_spspmm = psb_get_timer_idx("SPMM_BLD: par_spspmm") + + naggr = nlaggr(me+1) + ntaggr = sum(nlaggr) + naggrm1 = sum(nlaggr(1:me)) + naggrp1 = sum(nlaggr(1:me+1)) + !write(0,*)me,' ',name,' input sizes',nlaggr(:),':',naggr + + ! + ! 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_cprol%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_toc(idx_spspmm) + + if (debug) write(0,*) me,trim(name),' Done AxPROL ',& + & acsr3%get_nrows(),acsr3%get_ncols(), acsr3%get_nzeros(),& + & desc_cprol%get_local_rows(),desc_cprol%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%cp_to_lcoo(coo_restr,info) +!!$ write(0,*)me,' ',name,' new into transposition ',coo_restr%get_nrows(),& +!!$ & coo_restr%get_ncols(),coo_restr%get_nzeros() + call coo_restr%transp() + nzl = coo_restr%get_nzeros() + call desc_cprol%l2gip(coo_restr%ia(1:nzl),info) + i=0 + ! + ! 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(:) + ! + do k=1, nzl + if ((naggrm1 < coo_restr%ia(k)) .and.(coo_restr%ia(k) <= naggrp1)) 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) + 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() + + 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' + nzl = tmpcoo%get_nzeros() + call psb_glob_to_loc(tmpcoo%ia(1:nzl),desc_cprol,info,iact='I',owned=.true.) + call tmpcoo%clean_negidx(info) + nzl = tmpcoo%get_nzeros() + call tmpcoo%set_nrows(desc_cprol%get_local_rows()) + 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() + call csr_restr%mv_from_lcoo(tmpcoo,info) + + if (debug) write(0,*) me,trim(name),' Product RESTRxAP ',& + & csr_restr%get_nrows(),csr_restr%get_ncols(), & + & desc_cprol%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_cprol,info) + if (do_timings) call psb_toc(idx_spspmm) + call csr_restr%free() + call acsr3%free() + call ac_csr%mv_to_lcoo(ac_coo,info) + nza = ac_coo%get_nzeros() + if (debug) write(0,*) me,trim(name),' Fixing ac ',& + & ac_coo%get_nrows(),ac_coo%get_ncols(), nza + call ac_coo%fix(info) + call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) + call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) + call ac_coo%set_nrows(ntaggr) + call ac_coo%set_ncols(ntaggr) + if (debug) write(0,*) me,' ',trim(name),' Before mv_from',psb_get_errstatus() + 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),' ',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() + + nza = coo_prol%get_nzeros() + call desc_cprol%indxmap%l2gip(coo_prol%ja(1:nza),info) + + if (debug) then + write(0,*) me,' ',trim(name),' Checkpoint at exit' + call psb_barrier(ictxt) + write(0,*) me,' ',trim(name),' Checkpoint through' + end if + + if (info /= psb_success_) then + call psb_errpush(psb_err_internal_error_,name,a_err='Build ac = coo_restr x am3') + goto 9999 + end if + + + if (debug_level >= psb_debug_outer_) & + & write(debug_unit,*) me,' ',trim(name),& + & 'Done spmm_bld_inner ' + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + +end subroutine mld_c_spmm_bld_inner + +subroutine mld_lc_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& + & coo_prol,desc_cprol,coo_restr,info) + use psb_base_mod + use mld_c_inner_mod + use mld_c_base_aggregator_mod, mld_protect_name => mld_lc_spmm_bld_inner + implicit none + ! Arguments type(psb_lc_csr_sparse_mat), intent(inout) :: a_csr type(psb_desc_type), intent(in) :: desc_a @@ -210,4 +387,4 @@ subroutine mld_c_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& return -end subroutine mld_c_spmm_bld_inner +end subroutine mld_lc_spmm_bld_inner diff --git a/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 index c9cca92c..aeac233e 100644 --- a/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 @@ -42,6 +42,183 @@ subroutine mld_d_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& use mld_d_base_aggregator_mod, mld_protect_name => mld_d_spmm_bld_inner implicit none + ! Arguments + type(psb_d_csr_sparse_mat), intent(inout) :: a_csr + type(psb_desc_type), intent(in) :: desc_a + integer(psb_lpk_), intent(inout) :: nlaggr(:) + type(mld_dml_parms), intent(inout) :: parms + type(psb_ld_coo_sparse_mat), intent(inout) :: coo_prol, coo_restr + type(psb_desc_type), intent(inout) :: desc_cprol + type(psb_ldspmat_type), intent(out) :: ac + integer(psb_ipk_), intent(out) :: info + + ! Local variables + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ictxt,np,me, icomm, ndx, minfo + character(len=40) :: name + integer(psb_ipk_) :: ierr(5) + type(psb_ld_coo_sparse_mat) :: ac_coo, tmpcoo + type(psb_d_csr_sparse_mat) :: acsr3, csr_prol, ac_csr, csr_restr + integer(psb_ipk_) :: debug_level, debug_unit, naggr + integer(psb_lpk_) :: nrow, nglob, ncol, ntaggr, nzl, ip, & + & nzt, naggrm1, naggrp1, i, k + integer(psb_lpk_) :: nrsave, ncsave, nzsave, nza + logical, parameter :: do_timings=.true., oldstyle=.false., debug=.false. + integer(psb_ipk_), save :: idx_spspmm=-1 + + name='mld_spmm_bld_inner' + if(psb_get_errstatus().ne.0) return + info=psb_success_ + call psb_erractionsave(err_act) + + + ictxt = desc_a%get_context() + icomm = desc_a%get_mpic() + call psb_info(ictxt, me, np) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + nglob = desc_a%get_global_rows() + nrow = desc_a%get_local_rows() + ncol = desc_a%get_local_cols() + + if ((do_timings).and.(idx_spspmm==-1)) & + & idx_spspmm = psb_get_timer_idx("SPMM_BLD: par_spspmm") + + naggr = nlaggr(me+1) + ntaggr = sum(nlaggr) + naggrm1 = sum(nlaggr(1:me)) + naggrp1 = sum(nlaggr(1:me+1)) + !write(0,*)me,' ',name,' input sizes',nlaggr(:),':',naggr + + ! + ! 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_cprol%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_toc(idx_spspmm) + + if (debug) write(0,*) me,trim(name),' Done AxPROL ',& + & acsr3%get_nrows(),acsr3%get_ncols(), acsr3%get_nzeros(),& + & desc_cprol%get_local_rows(),desc_cprol%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%cp_to_lcoo(coo_restr,info) +!!$ write(0,*)me,' ',name,' new into transposition ',coo_restr%get_nrows(),& +!!$ & coo_restr%get_ncols(),coo_restr%get_nzeros() + call coo_restr%transp() + nzl = coo_restr%get_nzeros() + call desc_cprol%l2gip(coo_restr%ia(1:nzl),info) + i=0 + ! + ! 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(:) + ! + do k=1, nzl + if ((naggrm1 < coo_restr%ia(k)) .and.(coo_restr%ia(k) <= naggrp1)) 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) + 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() + + 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' + nzl = tmpcoo%get_nzeros() + call psb_glob_to_loc(tmpcoo%ia(1:nzl),desc_cprol,info,iact='I',owned=.true.) + call tmpcoo%clean_negidx(info) + nzl = tmpcoo%get_nzeros() + call tmpcoo%set_nrows(desc_cprol%get_local_rows()) + 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() + call csr_restr%mv_from_lcoo(tmpcoo,info) + + if (debug) write(0,*) me,trim(name),' Product RESTRxAP ',& + & csr_restr%get_nrows(),csr_restr%get_ncols(), & + & desc_cprol%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_cprol,info) + if (do_timings) call psb_toc(idx_spspmm) + call csr_restr%free() + call acsr3%free() + call ac_csr%mv_to_lcoo(ac_coo,info) + nza = ac_coo%get_nzeros() + if (debug) write(0,*) me,trim(name),' Fixing ac ',& + & ac_coo%get_nrows(),ac_coo%get_ncols(), nza + call ac_coo%fix(info) + call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) + call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) + call ac_coo%set_nrows(ntaggr) + call ac_coo%set_ncols(ntaggr) + if (debug) write(0,*) me,' ',trim(name),' Before mv_from',psb_get_errstatus() + 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),' ',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() + + nza = coo_prol%get_nzeros() + call desc_cprol%indxmap%l2gip(coo_prol%ja(1:nza),info) + + if (debug) then + write(0,*) me,' ',trim(name),' Checkpoint at exit' + call psb_barrier(ictxt) + write(0,*) me,' ',trim(name),' Checkpoint through' + end if + + if (info /= psb_success_) then + call psb_errpush(psb_err_internal_error_,name,a_err='Build ac = coo_restr x am3') + goto 9999 + end if + + + if (debug_level >= psb_debug_outer_) & + & write(debug_unit,*) me,' ',trim(name),& + & 'Done spmm_bld_inner ' + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + +end subroutine mld_d_spmm_bld_inner + +subroutine mld_ld_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& + & coo_prol,desc_cprol,coo_restr,info) + use psb_base_mod + use mld_d_inner_mod + use mld_d_base_aggregator_mod, mld_protect_name => mld_ld_spmm_bld_inner + implicit none + ! Arguments type(psb_ld_csr_sparse_mat), intent(inout) :: a_csr type(psb_desc_type), intent(in) :: desc_a @@ -210,4 +387,4 @@ subroutine mld_d_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& return -end subroutine mld_d_spmm_bld_inner +end subroutine mld_ld_spmm_bld_inner diff --git a/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 index 925f8207..0eff8d64 100644 --- a/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 @@ -42,6 +42,183 @@ subroutine mld_s_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& use mld_s_base_aggregator_mod, mld_protect_name => mld_s_spmm_bld_inner implicit none + ! Arguments + type(psb_s_csr_sparse_mat), intent(inout) :: a_csr + type(psb_desc_type), intent(in) :: desc_a + integer(psb_lpk_), intent(inout) :: nlaggr(:) + type(mld_sml_parms), intent(inout) :: parms + type(psb_ls_coo_sparse_mat), intent(inout) :: coo_prol, coo_restr + type(psb_desc_type), intent(inout) :: desc_cprol + type(psb_lsspmat_type), intent(out) :: ac + integer(psb_ipk_), intent(out) :: info + + ! Local variables + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ictxt,np,me, icomm, ndx, minfo + character(len=40) :: name + integer(psb_ipk_) :: ierr(5) + type(psb_ls_coo_sparse_mat) :: ac_coo, tmpcoo + type(psb_s_csr_sparse_mat) :: acsr3, csr_prol, ac_csr, csr_restr + integer(psb_ipk_) :: debug_level, debug_unit, naggr + integer(psb_lpk_) :: nrow, nglob, ncol, ntaggr, nzl, ip, & + & nzt, naggrm1, naggrp1, i, k + integer(psb_lpk_) :: nrsave, ncsave, nzsave, nza + logical, parameter :: do_timings=.true., oldstyle=.false., debug=.false. + integer(psb_ipk_), save :: idx_spspmm=-1 + + name='mld_spmm_bld_inner' + if(psb_get_errstatus().ne.0) return + info=psb_success_ + call psb_erractionsave(err_act) + + + ictxt = desc_a%get_context() + icomm = desc_a%get_mpic() + call psb_info(ictxt, me, np) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + nglob = desc_a%get_global_rows() + nrow = desc_a%get_local_rows() + ncol = desc_a%get_local_cols() + + if ((do_timings).and.(idx_spspmm==-1)) & + & idx_spspmm = psb_get_timer_idx("SPMM_BLD: par_spspmm") + + naggr = nlaggr(me+1) + ntaggr = sum(nlaggr) + naggrm1 = sum(nlaggr(1:me)) + naggrp1 = sum(nlaggr(1:me+1)) + !write(0,*)me,' ',name,' input sizes',nlaggr(:),':',naggr + + ! + ! 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_cprol%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_toc(idx_spspmm) + + if (debug) write(0,*) me,trim(name),' Done AxPROL ',& + & acsr3%get_nrows(),acsr3%get_ncols(), acsr3%get_nzeros(),& + & desc_cprol%get_local_rows(),desc_cprol%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%cp_to_lcoo(coo_restr,info) +!!$ write(0,*)me,' ',name,' new into transposition ',coo_restr%get_nrows(),& +!!$ & coo_restr%get_ncols(),coo_restr%get_nzeros() + call coo_restr%transp() + nzl = coo_restr%get_nzeros() + call desc_cprol%l2gip(coo_restr%ia(1:nzl),info) + i=0 + ! + ! 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(:) + ! + do k=1, nzl + if ((naggrm1 < coo_restr%ia(k)) .and.(coo_restr%ia(k) <= naggrp1)) 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) + 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() + + 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' + nzl = tmpcoo%get_nzeros() + call psb_glob_to_loc(tmpcoo%ia(1:nzl),desc_cprol,info,iact='I',owned=.true.) + call tmpcoo%clean_negidx(info) + nzl = tmpcoo%get_nzeros() + call tmpcoo%set_nrows(desc_cprol%get_local_rows()) + 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() + call csr_restr%mv_from_lcoo(tmpcoo,info) + + if (debug) write(0,*) me,trim(name),' Product RESTRxAP ',& + & csr_restr%get_nrows(),csr_restr%get_ncols(), & + & desc_cprol%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_cprol,info) + if (do_timings) call psb_toc(idx_spspmm) + call csr_restr%free() + call acsr3%free() + call ac_csr%mv_to_lcoo(ac_coo,info) + nza = ac_coo%get_nzeros() + if (debug) write(0,*) me,trim(name),' Fixing ac ',& + & ac_coo%get_nrows(),ac_coo%get_ncols(), nza + call ac_coo%fix(info) + call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) + call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) + call ac_coo%set_nrows(ntaggr) + call ac_coo%set_ncols(ntaggr) + if (debug) write(0,*) me,' ',trim(name),' Before mv_from',psb_get_errstatus() + 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),' ',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() + + nza = coo_prol%get_nzeros() + call desc_cprol%indxmap%l2gip(coo_prol%ja(1:nza),info) + + if (debug) then + write(0,*) me,' ',trim(name),' Checkpoint at exit' + call psb_barrier(ictxt) + write(0,*) me,' ',trim(name),' Checkpoint through' + end if + + if (info /= psb_success_) then + call psb_errpush(psb_err_internal_error_,name,a_err='Build ac = coo_restr x am3') + goto 9999 + end if + + + if (debug_level >= psb_debug_outer_) & + & write(debug_unit,*) me,' ',trim(name),& + & 'Done spmm_bld_inner ' + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + +end subroutine mld_s_spmm_bld_inner + +subroutine mld_ls_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& + & coo_prol,desc_cprol,coo_restr,info) + use psb_base_mod + use mld_s_inner_mod + use mld_s_base_aggregator_mod, mld_protect_name => mld_ls_spmm_bld_inner + implicit none + ! Arguments type(psb_ls_csr_sparse_mat), intent(inout) :: a_csr type(psb_desc_type), intent(in) :: desc_a @@ -210,4 +387,4 @@ subroutine mld_s_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& return -end subroutine mld_s_spmm_bld_inner +end subroutine mld_ls_spmm_bld_inner diff --git a/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 index d7f3308d..d664e1d1 100644 --- a/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 @@ -42,6 +42,183 @@ subroutine mld_z_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& use mld_z_base_aggregator_mod, mld_protect_name => mld_z_spmm_bld_inner implicit none + ! Arguments + type(psb_z_csr_sparse_mat), intent(inout) :: a_csr + type(psb_desc_type), intent(in) :: desc_a + integer(psb_lpk_), intent(inout) :: nlaggr(:) + type(mld_dml_parms), intent(inout) :: parms + type(psb_lz_coo_sparse_mat), intent(inout) :: coo_prol, coo_restr + type(psb_desc_type), intent(inout) :: desc_cprol + type(psb_lzspmat_type), intent(out) :: ac + integer(psb_ipk_), intent(out) :: info + + ! Local variables + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ictxt,np,me, icomm, ndx, minfo + character(len=40) :: name + integer(psb_ipk_) :: ierr(5) + type(psb_lz_coo_sparse_mat) :: ac_coo, tmpcoo + type(psb_z_csr_sparse_mat) :: acsr3, csr_prol, ac_csr, csr_restr + integer(psb_ipk_) :: debug_level, debug_unit, naggr + integer(psb_lpk_) :: nrow, nglob, ncol, ntaggr, nzl, ip, & + & nzt, naggrm1, naggrp1, i, k + integer(psb_lpk_) :: nrsave, ncsave, nzsave, nza + logical, parameter :: do_timings=.true., oldstyle=.false., debug=.false. + integer(psb_ipk_), save :: idx_spspmm=-1 + + name='mld_spmm_bld_inner' + if(psb_get_errstatus().ne.0) return + info=psb_success_ + call psb_erractionsave(err_act) + + + ictxt = desc_a%get_context() + icomm = desc_a%get_mpic() + call psb_info(ictxt, me, np) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + nglob = desc_a%get_global_rows() + nrow = desc_a%get_local_rows() + ncol = desc_a%get_local_cols() + + if ((do_timings).and.(idx_spspmm==-1)) & + & idx_spspmm = psb_get_timer_idx("SPMM_BLD: par_spspmm") + + naggr = nlaggr(me+1) + ntaggr = sum(nlaggr) + naggrm1 = sum(nlaggr(1:me)) + naggrp1 = sum(nlaggr(1:me+1)) + !write(0,*)me,' ',name,' input sizes',nlaggr(:),':',naggr + + ! + ! 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_cprol%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_toc(idx_spspmm) + + if (debug) write(0,*) me,trim(name),' Done AxPROL ',& + & acsr3%get_nrows(),acsr3%get_ncols(), acsr3%get_nzeros(),& + & desc_cprol%get_local_rows(),desc_cprol%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%cp_to_lcoo(coo_restr,info) +!!$ write(0,*)me,' ',name,' new into transposition ',coo_restr%get_nrows(),& +!!$ & coo_restr%get_ncols(),coo_restr%get_nzeros() + call coo_restr%transp() + nzl = coo_restr%get_nzeros() + call desc_cprol%l2gip(coo_restr%ia(1:nzl),info) + i=0 + ! + ! 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(:) + ! + do k=1, nzl + if ((naggrm1 < coo_restr%ia(k)) .and.(coo_restr%ia(k) <= naggrp1)) 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) + 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() + + 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' + nzl = tmpcoo%get_nzeros() + call psb_glob_to_loc(tmpcoo%ia(1:nzl),desc_cprol,info,iact='I',owned=.true.) + call tmpcoo%clean_negidx(info) + nzl = tmpcoo%get_nzeros() + call tmpcoo%set_nrows(desc_cprol%get_local_rows()) + 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() + call csr_restr%mv_from_lcoo(tmpcoo,info) + + if (debug) write(0,*) me,trim(name),' Product RESTRxAP ',& + & csr_restr%get_nrows(),csr_restr%get_ncols(), & + & desc_cprol%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_cprol,info) + if (do_timings) call psb_toc(idx_spspmm) + call csr_restr%free() + call acsr3%free() + call ac_csr%mv_to_lcoo(ac_coo,info) + nza = ac_coo%get_nzeros() + if (debug) write(0,*) me,trim(name),' Fixing ac ',& + & ac_coo%get_nrows(),ac_coo%get_ncols(), nza + call ac_coo%fix(info) + call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) + call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) + call ac_coo%set_nrows(ntaggr) + call ac_coo%set_ncols(ntaggr) + if (debug) write(0,*) me,' ',trim(name),' Before mv_from',psb_get_errstatus() + 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),' ',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() + + nza = coo_prol%get_nzeros() + call desc_cprol%indxmap%l2gip(coo_prol%ja(1:nza),info) + + if (debug) then + write(0,*) me,' ',trim(name),' Checkpoint at exit' + call psb_barrier(ictxt) + write(0,*) me,' ',trim(name),' Checkpoint through' + end if + + if (info /= psb_success_) then + call psb_errpush(psb_err_internal_error_,name,a_err='Build ac = coo_restr x am3') + goto 9999 + end if + + + if (debug_level >= psb_debug_outer_) & + & write(debug_unit,*) me,' ',trim(name),& + & 'Done spmm_bld_inner ' + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + +end subroutine mld_z_spmm_bld_inner + +subroutine mld_lz_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& + & coo_prol,desc_cprol,coo_restr,info) + use psb_base_mod + use mld_z_inner_mod + use mld_z_base_aggregator_mod, mld_protect_name => mld_lz_spmm_bld_inner + implicit none + ! Arguments type(psb_lz_csr_sparse_mat), intent(inout) :: a_csr type(psb_desc_type), intent(in) :: desc_a @@ -210,4 +387,4 @@ subroutine mld_z_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& return -end subroutine mld_z_spmm_bld_inner +end subroutine mld_lz_spmm_bld_inner diff --git a/mlprec/mld_c_base_aggregator_mod.f90 b/mlprec/mld_c_base_aggregator_mod.f90 index d71607e1..3d0eaa95 100644 --- a/mlprec/mld_c_base_aggregator_mod.f90 +++ b/mlprec/mld_c_base_aggregator_mod.f90 @@ -43,8 +43,10 @@ module mld_c_base_aggregator_mod use mld_base_prec_type, only : mld_sml_parms, mld_saggr_data 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_lc_csr_sparse_mat, & - & psb_lc_coo_sparse_mat, psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, & + & psb_c_base_vect_type, psb_clinmap_type, psb_spk_, & + & psb_lc_csr_sparse_mat, psb_lc_coo_sparse_mat, & + & psb_c_csr_sparse_mat, psb_c_coo_sparse_mat, & + & psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, & & psb_erractionsave, psb_error_handler, psb_success_, psb_toupper ! ! @@ -121,6 +123,20 @@ module mld_c_base_aggregator_mod interface mld_spmm_bld_inner subroutine mld_c_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& & coo_prol,desc_cprol,coo_restr,info) + import :: psb_c_csr_sparse_mat, psb_lcspmat_type, psb_desc_type, & + & psb_lc_coo_sparse_mat, mld_sml_parms, psb_spk_, psb_ipk_, psb_lpk_ + implicit none + type(psb_c_csr_sparse_mat), intent(inout) :: a_csr + type(psb_desc_type), intent(in) :: desc_a + integer(psb_lpk_), intent(inout) :: nlaggr(:) + type(mld_sml_parms), intent(inout) :: parms + type(psb_lc_coo_sparse_mat), intent(inout) :: coo_prol, coo_restr + type(psb_desc_type), intent(inout) :: desc_cprol + type(psb_lcspmat_type), intent(out) :: ac + integer(psb_ipk_), intent(out) :: info + end subroutine mld_c_spmm_bld_inner + subroutine mld_lc_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& + & coo_prol,desc_cprol,coo_restr,info) import :: psb_lc_csr_sparse_mat, psb_lcspmat_type, psb_desc_type, & & psb_lc_coo_sparse_mat, mld_sml_parms, psb_spk_, psb_ipk_, psb_lpk_ implicit none @@ -132,7 +148,7 @@ module mld_c_base_aggregator_mod type(psb_desc_type), intent(inout) :: desc_cprol type(psb_lcspmat_type), intent(out) :: ac integer(psb_ipk_), intent(out) :: info - end subroutine mld_c_spmm_bld_inner + end subroutine mld_lc_spmm_bld_inner end interface mld_spmm_bld_inner contains diff --git a/mlprec/mld_d_base_aggregator_mod.f90 b/mlprec/mld_d_base_aggregator_mod.f90 index 2785a805..4e788975 100644 --- a/mlprec/mld_d_base_aggregator_mod.f90 +++ b/mlprec/mld_d_base_aggregator_mod.f90 @@ -43,8 +43,10 @@ module mld_d_base_aggregator_mod use mld_base_prec_type, only : mld_dml_parms, mld_daggr_data 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_ld_csr_sparse_mat, & - & psb_ld_coo_sparse_mat, psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, & + & psb_d_base_vect_type, psb_dlinmap_type, psb_dpk_, & + & psb_ld_csr_sparse_mat, psb_ld_coo_sparse_mat, & + & psb_d_csr_sparse_mat, psb_d_coo_sparse_mat, & + & psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, & & psb_erractionsave, psb_error_handler, psb_success_, psb_toupper ! ! @@ -121,6 +123,20 @@ module mld_d_base_aggregator_mod interface mld_spmm_bld_inner subroutine mld_d_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& & coo_prol,desc_cprol,coo_restr,info) + import :: psb_d_csr_sparse_mat, psb_ldspmat_type, psb_desc_type, & + & psb_ld_coo_sparse_mat, mld_dml_parms, psb_dpk_, psb_ipk_, psb_lpk_ + implicit none + type(psb_d_csr_sparse_mat), intent(inout) :: a_csr + type(psb_desc_type), intent(in) :: desc_a + integer(psb_lpk_), intent(inout) :: nlaggr(:) + type(mld_dml_parms), intent(inout) :: parms + type(psb_ld_coo_sparse_mat), intent(inout) :: coo_prol, coo_restr + type(psb_desc_type), intent(inout) :: desc_cprol + type(psb_ldspmat_type), intent(out) :: ac + integer(psb_ipk_), intent(out) :: info + end subroutine mld_d_spmm_bld_inner + subroutine mld_ld_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& + & coo_prol,desc_cprol,coo_restr,info) import :: psb_ld_csr_sparse_mat, psb_ldspmat_type, psb_desc_type, & & psb_ld_coo_sparse_mat, mld_dml_parms, psb_dpk_, psb_ipk_, psb_lpk_ implicit none @@ -132,7 +148,7 @@ module mld_d_base_aggregator_mod type(psb_desc_type), intent(inout) :: desc_cprol type(psb_ldspmat_type), intent(out) :: ac integer(psb_ipk_), intent(out) :: info - end subroutine mld_d_spmm_bld_inner + end subroutine mld_ld_spmm_bld_inner end interface mld_spmm_bld_inner contains diff --git a/mlprec/mld_s_base_aggregator_mod.f90 b/mlprec/mld_s_base_aggregator_mod.f90 index d3fdad1f..1dff55c1 100644 --- a/mlprec/mld_s_base_aggregator_mod.f90 +++ b/mlprec/mld_s_base_aggregator_mod.f90 @@ -43,8 +43,10 @@ module mld_s_base_aggregator_mod use mld_base_prec_type, only : mld_sml_parms, mld_saggr_data 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_ls_csr_sparse_mat, & - & psb_ls_coo_sparse_mat, psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, & + & psb_s_base_vect_type, psb_slinmap_type, psb_spk_, & + & psb_ls_csr_sparse_mat, psb_ls_coo_sparse_mat, & + & psb_s_csr_sparse_mat, psb_s_coo_sparse_mat, & + & psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, & & psb_erractionsave, psb_error_handler, psb_success_, psb_toupper ! ! @@ -121,6 +123,20 @@ module mld_s_base_aggregator_mod interface mld_spmm_bld_inner subroutine mld_s_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& & coo_prol,desc_cprol,coo_restr,info) + import :: psb_s_csr_sparse_mat, psb_lsspmat_type, psb_desc_type, & + & psb_ls_coo_sparse_mat, mld_sml_parms, psb_spk_, psb_ipk_, psb_lpk_ + implicit none + type(psb_s_csr_sparse_mat), intent(inout) :: a_csr + type(psb_desc_type), intent(in) :: desc_a + integer(psb_lpk_), intent(inout) :: nlaggr(:) + type(mld_sml_parms), intent(inout) :: parms + type(psb_ls_coo_sparse_mat), intent(inout) :: coo_prol, coo_restr + type(psb_desc_type), intent(inout) :: desc_cprol + type(psb_lsspmat_type), intent(out) :: ac + integer(psb_ipk_), intent(out) :: info + end subroutine mld_s_spmm_bld_inner + subroutine mld_ls_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& + & coo_prol,desc_cprol,coo_restr,info) import :: psb_ls_csr_sparse_mat, psb_lsspmat_type, psb_desc_type, & & psb_ls_coo_sparse_mat, mld_sml_parms, psb_spk_, psb_ipk_, psb_lpk_ implicit none @@ -132,7 +148,7 @@ module mld_s_base_aggregator_mod type(psb_desc_type), intent(inout) :: desc_cprol type(psb_lsspmat_type), intent(out) :: ac integer(psb_ipk_), intent(out) :: info - end subroutine mld_s_spmm_bld_inner + end subroutine mld_ls_spmm_bld_inner end interface mld_spmm_bld_inner contains diff --git a/mlprec/mld_z_base_aggregator_mod.f90 b/mlprec/mld_z_base_aggregator_mod.f90 index b5c349e3..ba5cc2dd 100644 --- a/mlprec/mld_z_base_aggregator_mod.f90 +++ b/mlprec/mld_z_base_aggregator_mod.f90 @@ -43,8 +43,10 @@ module mld_z_base_aggregator_mod use mld_base_prec_type, only : mld_dml_parms, mld_daggr_data 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_lz_csr_sparse_mat, & - & psb_lz_coo_sparse_mat, psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, & + & psb_z_base_vect_type, psb_zlinmap_type, psb_dpk_, & + & psb_lz_csr_sparse_mat, psb_lz_coo_sparse_mat, & + & psb_z_csr_sparse_mat, psb_z_coo_sparse_mat, & + & psb_ipk_, psb_epk_, psb_lpk_, psb_desc_type, psb_i_base_vect_type, & & psb_erractionsave, psb_error_handler, psb_success_, psb_toupper ! ! @@ -121,6 +123,20 @@ module mld_z_base_aggregator_mod interface mld_spmm_bld_inner subroutine mld_z_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& & coo_prol,desc_cprol,coo_restr,info) + import :: psb_z_csr_sparse_mat, psb_lzspmat_type, psb_desc_type, & + & psb_lz_coo_sparse_mat, mld_dml_parms, psb_dpk_, psb_ipk_, psb_lpk_ + implicit none + type(psb_z_csr_sparse_mat), intent(inout) :: a_csr + type(psb_desc_type), intent(in) :: desc_a + integer(psb_lpk_), intent(inout) :: nlaggr(:) + type(mld_dml_parms), intent(inout) :: parms + type(psb_lz_coo_sparse_mat), intent(inout) :: coo_prol, coo_restr + type(psb_desc_type), intent(inout) :: desc_cprol + type(psb_lzspmat_type), intent(out) :: ac + integer(psb_ipk_), intent(out) :: info + end subroutine mld_z_spmm_bld_inner + subroutine mld_lz_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& + & coo_prol,desc_cprol,coo_restr,info) import :: psb_lz_csr_sparse_mat, psb_lzspmat_type, psb_desc_type, & & psb_lz_coo_sparse_mat, mld_dml_parms, psb_dpk_, psb_ipk_, psb_lpk_ implicit none @@ -132,7 +148,7 @@ module mld_z_base_aggregator_mod type(psb_desc_type), intent(inout) :: desc_cprol type(psb_lzspmat_type), intent(out) :: ac integer(psb_ipk_), intent(out) :: info - end subroutine mld_z_spmm_bld_inner + end subroutine mld_lz_spmm_bld_inner end interface mld_spmm_bld_inner contains From 28cc3283cdd118ed578cb9151d9d7f715d15b6c4 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Wed, 15 Apr 2020 09:50:57 +0200 Subject: [PATCH 02/11] Update makefile for cbind. --- cbind/mlprec/Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cbind/mlprec/Makefile b/cbind/mlprec/Makefile index 37231cda..21f7db31 100644 --- a/cbind/mlprec/Makefile +++ b/cbind/mlprec/Makefile @@ -14,7 +14,7 @@ OBJS=mld_prec_cbind_mod.o mld_dprec_cbind_mod.o mld_c_dprec.o mld_zprec_cbind_m CMOD=mld_cbind.h mld_c_dprec.h mld_c_zprec.h mld_const.h -LIBMOD=mld_prec_cbind_mod$(.mod) +LIBMOD=mld_prec_cbind_mod$(.mod) mld_dprec_cbind_mod$(.mod) mld_zprec_cbind_mod$(.mod) LOCAL_MODS=$(LIBMOD) #LIBNAME=$(CPRECLIBNAME) From aa6c9df52f057ddd26a566608ab9f2b220d7e96f Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Wed, 15 Apr 2020 09:51:57 +0200 Subject: [PATCH 03/11] Fix cbind Makefile --- cbind/mlprec/Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cbind/mlprec/Makefile b/cbind/mlprec/Makefile index 37231cda..21f7db31 100644 --- a/cbind/mlprec/Makefile +++ b/cbind/mlprec/Makefile @@ -14,7 +14,7 @@ OBJS=mld_prec_cbind_mod.o mld_dprec_cbind_mod.o mld_c_dprec.o mld_zprec_cbind_m CMOD=mld_cbind.h mld_c_dprec.h mld_c_zprec.h mld_const.h -LIBMOD=mld_prec_cbind_mod$(.mod) +LIBMOD=mld_prec_cbind_mod$(.mod) mld_dprec_cbind_mod$(.mod) mld_zprec_cbind_mod$(.mod) LOCAL_MODS=$(LIBMOD) #LIBNAME=$(CPRECLIBNAME) From e4e7d8970ef246d3605227131deca512e9d699c3 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 17 Apr 2020 16:22:42 +0200 Subject: [PATCH 04/11] Move call to ac%fix --- mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 | 2 +- mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 | 2 +- mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 | 2 +- mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 index d06878de..0e75eb30 100644 --- a/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 @@ -170,10 +170,10 @@ subroutine mld_c_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& call csr_restr%free() call acsr3%free() call ac_csr%mv_to_lcoo(ac_coo,info) + call ac_coo%fix(info) nza = ac_coo%get_nzeros() if (debug) write(0,*) me,trim(name),' Fixing ac ',& & ac_coo%get_nrows(),ac_coo%get_ncols(), nza - call ac_coo%fix(info) call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) call ac_coo%set_nrows(ntaggr) diff --git a/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 index aeac233e..0d85c647 100644 --- a/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 @@ -170,10 +170,10 @@ subroutine mld_d_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& call csr_restr%free() call acsr3%free() call ac_csr%mv_to_lcoo(ac_coo,info) + call ac_coo%fix(info) nza = ac_coo%get_nzeros() if (debug) write(0,*) me,trim(name),' Fixing ac ',& & ac_coo%get_nrows(),ac_coo%get_ncols(), nza - call ac_coo%fix(info) call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) call ac_coo%set_nrows(ntaggr) diff --git a/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 index 0eff8d64..4ae68bbb 100644 --- a/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 @@ -170,10 +170,10 @@ subroutine mld_s_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& call csr_restr%free() call acsr3%free() call ac_csr%mv_to_lcoo(ac_coo,info) + call ac_coo%fix(info) nza = ac_coo%get_nzeros() if (debug) write(0,*) me,trim(name),' Fixing ac ',& & ac_coo%get_nrows(),ac_coo%get_ncols(), nza - call ac_coo%fix(info) call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) call ac_coo%set_nrows(ntaggr) diff --git a/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 index d664e1d1..98aa63f2 100644 --- a/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 @@ -170,10 +170,10 @@ subroutine mld_z_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& call csr_restr%free() call acsr3%free() call ac_csr%mv_to_lcoo(ac_coo,info) + call ac_coo%fix(info) nza = ac_coo%get_nzeros() if (debug) write(0,*) me,trim(name),' Fixing ac ',& & ac_coo%get_nrows(),ac_coo%get_ncols(), nza - call ac_coo%fix(info) call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) call ac_coo%set_nrows(ntaggr) From d2aeeb9dae1cad6d93fb58bf1a56b656ac0d04d6 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Sat, 18 Apr 2020 17:59:36 +0200 Subject: [PATCH 05/11] Improve structure of Makefiles --- Makefile | 4 ++-- cbind/Makefile | 4 ++-- mlprec/Makefile | 4 ++-- mlprec/impl/Makefile | 16 ++++++++-------- 4 files changed, 14 insertions(+), 14 deletions(-) diff --git a/Makefile b/Makefile index 24e08cc2..8e727371 100644 --- a/Makefile +++ b/Makefile @@ -13,9 +13,9 @@ libdir: mlp: - cd mlprec && $(MAKE) all + $(MAKE) -C mlprec all cbnd: mlp - cd cbind && $(MAKE) all + $(MAKE) -C cbind all install: all mkdir -p $(INSTALL_LIBDIR) &&\ $(INSTALL_DATA) lib/*.a $(INSTALL_LIBDIR) diff --git a/cbind/Makefile b/cbind/Makefile index 663fda86..a7cc9917 100644 --- a/cbind/Makefile +++ b/cbind/Makefile @@ -15,11 +15,11 @@ lib: mlprecd mlprecd: - cd mlprec && $(MAKE) lib LIBNAME=$(LIBNAME) + $(MAKE) -C mlprec lib LIBNAME=$(LIBNAME) clean: - cd mlprec && $(MAKE) clean + $(MAKE) -C mlprec clean veryclean: clean diff --git a/mlprec/Makefile b/mlprec/Makefile index 7b5b3d24..76a4a699 100644 --- a/mlprec/Makefile +++ b/mlprec/Makefile @@ -55,7 +55,7 @@ LIBNAME=libmld_prec.a all: lib impld impld: $(OBJS) - cd impl && $(MAKE) + $(MAKE) -C impl lib: $(OBJS) impld $(AR) $(HERE)/$(LIBNAME) $(OBJS) @@ -172,4 +172,4 @@ clean: implclean /bin/rm -f $(OBJS) $(LOCAL_MODS) *$(.mod) implclean: - cd impl && $(MAKE) clean + $(MAKE) -C impl clean diff --git a/mlprec/impl/Makefile b/mlprec/impl/Makefile index 27842294..3a527d23 100644 --- a/mlprec/impl/Makefile +++ b/mlprec/impl/Makefile @@ -72,13 +72,13 @@ lib: $(OBJS) aggrd levd smoothd solvd $(RANLIB) $(HERE)/$(LIBNAME) aggrd: - cd aggregator && $(MAKE) + $(MAKE) -C aggregator levd: - cd level && $(MAKE) + $(MAKE) -C level smoothd: - cd smoother && $(MAKE) + $(MAKE) -C smoother solvd: - cd solver && $(MAKE) + $(MAKE) -C solver mpobjs: (make $(MPFOBJS) FC="$(MPFC)" FCOPT="$(FCOPT)") @@ -91,10 +91,10 @@ clean: solvclean smoothclean levclean aggrclean /bin/rm -f $(OBJS) $(LOCAL_MODS) aggrclean: - cd aggregator && $(MAKE) clean + $(MAKE) -C aggregator clean levclean: - cd level && $(MAKE) clean + $(MAKE) -C level clean smoothclean: - cd smoother && $(MAKE) clean + $(MAKE) -C smoother clean solvclean: - cd solver && $(MAKE) clean + $(MAKE) -C solver clean From 028ccea2e378e3399aa0c30f553afad7cb4acf2e Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Wed, 22 Apr 2020 10:37:56 +0100 Subject: [PATCH 06/11] Fix handling of aggregator/smoother parms upon resizing --- mlprec/impl/mld_c_hierarchy_bld.f90 | 43 ++++++++++++++++------------- mlprec/impl/mld_d_hierarchy_bld.f90 | 43 ++++++++++++++++------------- mlprec/impl/mld_s_hierarchy_bld.f90 | 43 ++++++++++++++++------------- mlprec/impl/mld_z_hierarchy_bld.f90 | 43 ++++++++++++++++------------- 4 files changed, 96 insertions(+), 76 deletions(-) diff --git a/mlprec/impl/mld_c_hierarchy_bld.f90 b/mlprec/impl/mld_c_hierarchy_bld.f90 index f9678195..c05e4c41 100644 --- a/mlprec/impl/mld_c_hierarchy_bld.f90 +++ b/mlprec/impl/mld_c_hierarchy_bld.f90 @@ -83,15 +83,17 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info) & nplevs, mxplevs integer(psb_lpk_) :: iaggsize, casize real(psb_spk_) :: mnaggratio, sizeratio, athresh, aomega - class(mld_c_base_smoother_type), allocatable :: coarse_sm, base_sm, med_sm, & - & base_sm2, med_sm2, coarse_sm2 + class(mld_c_base_smoother_type), allocatable :: coarse_sm, med_sm, & + & med_sm2, coarse_sm2 class(mld_c_base_aggregator_type), allocatable :: tmp_aggr - type(mld_sml_parms) :: baseparms, medparms, coarseparms + type(mld_sml_parms) :: medparms, coarseparms integer(psb_lpk_), allocatable :: ilaggr(:), nlaggr(:) type(psb_lcspmat_type) :: op_prol type(mld_c_onelev_type), allocatable :: tprecv(:) integer(psb_ipk_) :: debug_level, debug_unit character(len=20) :: name, ch_err + integer(psb_ipk_), save :: idx_bldtp=-1, idx_matasb=-1 + logical, parameter :: do_timings=.false. info=psb_success_ err=0 @@ -110,6 +112,10 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info) if (debug_level >= psb_debug_outer_) & & write(debug_unit,*) me,' ',trim(name),& & 'Entering ' + if ((do_timings).and.(idx_bldtp==-1)) & + & idx_bldtp = psb_get_timer_idx("BLD_HIER: bld_tprol") + if ((do_timings).and.(idx_matasb==-1)) & + & idx_matasb = psb_get_timer_idx("BLD_HIER: mmat_asb") ! if (.not.allocated(prec%precv)) then @@ -207,15 +213,12 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info) end if nplevs = max(itwo,mxplevs) + ! + ! The coarse parameters will be needed later + ! coarseparms = prec%precv(iszv)%parms - baseparms = prec%precv(1)%parms - medparms = prec%precv(2)%parms - call save_smoothers(prec%precv(iszv),coarse_sm,coarse_sm2,info) - if (info == 0) call save_smoothers(prec%precv(2),med_sm,med_sm2,info) - if (info == 0) call save_smoothers(prec%precv(1),base_sm,base_sm2,info) if (info /= psb_success_) then - write(0,*) 'Error in saving smoothers',info call psb_errpush(psb_err_internal_error_,name,a_err='Base level precbuild.') goto 9999 end if @@ -225,19 +228,17 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info) if (iszv /= nplevs) then allocate(tprecv(nplevs),stat=info) ! First all existing levels - if (info == 0) tprecv(1)%parms = baseparms - if (info == 0) call restore_smoothers(tprecv(1),& - & prec%precv(1)%sm,prec%precv(1)%sm2a,info) - if (info == 0) call move_alloc(prec%precv(1)%aggr,tprecv(1)%aggr) - do i=2, min(iszv,nplevs) - 1 - if (info == 0) tprecv(i)%parms = medparms + do i=1, min(iszv,nplevs) - 1 + if (info == 0) tprecv(i)%parms = prec%precv(i)%parms if (info == 0) call restore_smoothers(tprecv(i),& & prec%precv(i)%sm,prec%precv(i)%sm2a,info) if (info == 0) call move_alloc(prec%precv(i)%aggr,tprecv(i)%aggr) end do if (iszv < nplevs) then + ! Further intermediates, if needed allocate(tmp_aggr,source=tprecv(iszv-1)%aggr,stat=info) - ! Further intermediates, if any + medparms = prec%precv(iszv-1)%parms + call save_smoothers(prec%precv(iszv-1),med_sm,med_sm2,info) do i=iszv, nplevs - 1 if (info == 0) tprecv(i)%parms = medparms if (info == 0) call restore_smoothers(tprecv(i),med_sm,med_sm2,info) @@ -302,11 +303,12 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info) ! Build the mapping between levels i-1 and i and the matrix ! at level i ! + if (do_timings) call psb_tic(idx_bldtp) if (info == psb_success_)& & call prec%precv(i)%bld_tprol(prec%precv(i-1)%base_a,& & prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,prec%ag_data,info) - + if (do_timings) call psb_toc(idx_bldtp) if (info /= psb_success_) then call psb_errpush(psb_err_internal_error_,name,& & a_err='Map build') @@ -387,20 +389,23 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info) nlaggr = prec%precv(newsz)%map%naggr call prec%precv(newsz)%tprol%clone(op_prol,info) end if - + if (do_timings) call psb_tic(idx_matasb) if (info == psb_success_) call prec%precv(newsz)%mat_asb( & & prec%precv(newsz-1)%base_a,prec%precv(newsz-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) + if (do_timings) call psb_toc(idx_matasb) if (info /= 0) then call psb_errpush(psb_err_internal_error_,name,& & a_err='Mat asb') goto 9999 endif exit array_build_loop - else + else + if (do_timings) call psb_tic(idx_matasb) if (info == psb_success_) call prec%precv(i)%mat_asb(& & prec%precv(i-1)%base_a,prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) + if (do_timings) call psb_toc(idx_matasb) end if if (info /= psb_success_) then call psb_errpush(psb_err_internal_error_,name,& diff --git a/mlprec/impl/mld_d_hierarchy_bld.f90 b/mlprec/impl/mld_d_hierarchy_bld.f90 index ca76f75d..0d6d174a 100644 --- a/mlprec/impl/mld_d_hierarchy_bld.f90 +++ b/mlprec/impl/mld_d_hierarchy_bld.f90 @@ -83,15 +83,17 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info) & nplevs, mxplevs integer(psb_lpk_) :: iaggsize, casize real(psb_dpk_) :: mnaggratio, sizeratio, athresh, aomega - class(mld_d_base_smoother_type), allocatable :: coarse_sm, base_sm, med_sm, & - & base_sm2, med_sm2, coarse_sm2 + class(mld_d_base_smoother_type), allocatable :: coarse_sm, med_sm, & + & med_sm2, coarse_sm2 class(mld_d_base_aggregator_type), allocatable :: tmp_aggr - type(mld_dml_parms) :: baseparms, medparms, coarseparms + type(mld_dml_parms) :: medparms, coarseparms integer(psb_lpk_), allocatable :: ilaggr(:), nlaggr(:) type(psb_ldspmat_type) :: op_prol type(mld_d_onelev_type), allocatable :: tprecv(:) integer(psb_ipk_) :: debug_level, debug_unit character(len=20) :: name, ch_err + integer(psb_ipk_), save :: idx_bldtp=-1, idx_matasb=-1 + logical, parameter :: do_timings=.false. info=psb_success_ err=0 @@ -110,6 +112,10 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info) if (debug_level >= psb_debug_outer_) & & write(debug_unit,*) me,' ',trim(name),& & 'Entering ' + if ((do_timings).and.(idx_bldtp==-1)) & + & idx_bldtp = psb_get_timer_idx("BLD_HIER: bld_tprol") + if ((do_timings).and.(idx_matasb==-1)) & + & idx_matasb = psb_get_timer_idx("BLD_HIER: mmat_asb") ! if (.not.allocated(prec%precv)) then @@ -207,15 +213,12 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info) end if nplevs = max(itwo,mxplevs) + ! + ! The coarse parameters will be needed later + ! coarseparms = prec%precv(iszv)%parms - baseparms = prec%precv(1)%parms - medparms = prec%precv(2)%parms - call save_smoothers(prec%precv(iszv),coarse_sm,coarse_sm2,info) - if (info == 0) call save_smoothers(prec%precv(2),med_sm,med_sm2,info) - if (info == 0) call save_smoothers(prec%precv(1),base_sm,base_sm2,info) if (info /= psb_success_) then - write(0,*) 'Error in saving smoothers',info call psb_errpush(psb_err_internal_error_,name,a_err='Base level precbuild.') goto 9999 end if @@ -225,19 +228,17 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info) if (iszv /= nplevs) then allocate(tprecv(nplevs),stat=info) ! First all existing levels - if (info == 0) tprecv(1)%parms = baseparms - if (info == 0) call restore_smoothers(tprecv(1),& - & prec%precv(1)%sm,prec%precv(1)%sm2a,info) - if (info == 0) call move_alloc(prec%precv(1)%aggr,tprecv(1)%aggr) - do i=2, min(iszv,nplevs) - 1 - if (info == 0) tprecv(i)%parms = medparms + do i=1, min(iszv,nplevs) - 1 + if (info == 0) tprecv(i)%parms = prec%precv(i)%parms if (info == 0) call restore_smoothers(tprecv(i),& & prec%precv(i)%sm,prec%precv(i)%sm2a,info) if (info == 0) call move_alloc(prec%precv(i)%aggr,tprecv(i)%aggr) end do if (iszv < nplevs) then + ! Further intermediates, if needed allocate(tmp_aggr,source=tprecv(iszv-1)%aggr,stat=info) - ! Further intermediates, if any + medparms = prec%precv(iszv-1)%parms + call save_smoothers(prec%precv(iszv-1),med_sm,med_sm2,info) do i=iszv, nplevs - 1 if (info == 0) tprecv(i)%parms = medparms if (info == 0) call restore_smoothers(tprecv(i),med_sm,med_sm2,info) @@ -302,11 +303,12 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info) ! Build the mapping between levels i-1 and i and the matrix ! at level i ! + if (do_timings) call psb_tic(idx_bldtp) if (info == psb_success_)& & call prec%precv(i)%bld_tprol(prec%precv(i-1)%base_a,& & prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,prec%ag_data,info) - + if (do_timings) call psb_toc(idx_bldtp) if (info /= psb_success_) then call psb_errpush(psb_err_internal_error_,name,& & a_err='Map build') @@ -387,20 +389,23 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info) nlaggr = prec%precv(newsz)%map%naggr call prec%precv(newsz)%tprol%clone(op_prol,info) end if - + if (do_timings) call psb_tic(idx_matasb) if (info == psb_success_) call prec%precv(newsz)%mat_asb( & & prec%precv(newsz-1)%base_a,prec%precv(newsz-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) + if (do_timings) call psb_toc(idx_matasb) if (info /= 0) then call psb_errpush(psb_err_internal_error_,name,& & a_err='Mat asb') goto 9999 endif exit array_build_loop - else + else + if (do_timings) call psb_tic(idx_matasb) if (info == psb_success_) call prec%precv(i)%mat_asb(& & prec%precv(i-1)%base_a,prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) + if (do_timings) call psb_toc(idx_matasb) end if if (info /= psb_success_) then call psb_errpush(psb_err_internal_error_,name,& diff --git a/mlprec/impl/mld_s_hierarchy_bld.f90 b/mlprec/impl/mld_s_hierarchy_bld.f90 index 91e24322..5669e758 100644 --- a/mlprec/impl/mld_s_hierarchy_bld.f90 +++ b/mlprec/impl/mld_s_hierarchy_bld.f90 @@ -83,15 +83,17 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info) & nplevs, mxplevs integer(psb_lpk_) :: iaggsize, casize real(psb_spk_) :: mnaggratio, sizeratio, athresh, aomega - class(mld_s_base_smoother_type), allocatable :: coarse_sm, base_sm, med_sm, & - & base_sm2, med_sm2, coarse_sm2 + class(mld_s_base_smoother_type), allocatable :: coarse_sm, med_sm, & + & med_sm2, coarse_sm2 class(mld_s_base_aggregator_type), allocatable :: tmp_aggr - type(mld_sml_parms) :: baseparms, medparms, coarseparms + type(mld_sml_parms) :: medparms, coarseparms integer(psb_lpk_), allocatable :: ilaggr(:), nlaggr(:) type(psb_lsspmat_type) :: op_prol type(mld_s_onelev_type), allocatable :: tprecv(:) integer(psb_ipk_) :: debug_level, debug_unit character(len=20) :: name, ch_err + integer(psb_ipk_), save :: idx_bldtp=-1, idx_matasb=-1 + logical, parameter :: do_timings=.false. info=psb_success_ err=0 @@ -110,6 +112,10 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info) if (debug_level >= psb_debug_outer_) & & write(debug_unit,*) me,' ',trim(name),& & 'Entering ' + if ((do_timings).and.(idx_bldtp==-1)) & + & idx_bldtp = psb_get_timer_idx("BLD_HIER: bld_tprol") + if ((do_timings).and.(idx_matasb==-1)) & + & idx_matasb = psb_get_timer_idx("BLD_HIER: mmat_asb") ! if (.not.allocated(prec%precv)) then @@ -207,15 +213,12 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info) end if nplevs = max(itwo,mxplevs) + ! + ! The coarse parameters will be needed later + ! coarseparms = prec%precv(iszv)%parms - baseparms = prec%precv(1)%parms - medparms = prec%precv(2)%parms - call save_smoothers(prec%precv(iszv),coarse_sm,coarse_sm2,info) - if (info == 0) call save_smoothers(prec%precv(2),med_sm,med_sm2,info) - if (info == 0) call save_smoothers(prec%precv(1),base_sm,base_sm2,info) if (info /= psb_success_) then - write(0,*) 'Error in saving smoothers',info call psb_errpush(psb_err_internal_error_,name,a_err='Base level precbuild.') goto 9999 end if @@ -225,19 +228,17 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info) if (iszv /= nplevs) then allocate(tprecv(nplevs),stat=info) ! First all existing levels - if (info == 0) tprecv(1)%parms = baseparms - if (info == 0) call restore_smoothers(tprecv(1),& - & prec%precv(1)%sm,prec%precv(1)%sm2a,info) - if (info == 0) call move_alloc(prec%precv(1)%aggr,tprecv(1)%aggr) - do i=2, min(iszv,nplevs) - 1 - if (info == 0) tprecv(i)%parms = medparms + do i=1, min(iszv,nplevs) - 1 + if (info == 0) tprecv(i)%parms = prec%precv(i)%parms if (info == 0) call restore_smoothers(tprecv(i),& & prec%precv(i)%sm,prec%precv(i)%sm2a,info) if (info == 0) call move_alloc(prec%precv(i)%aggr,tprecv(i)%aggr) end do if (iszv < nplevs) then + ! Further intermediates, if needed allocate(tmp_aggr,source=tprecv(iszv-1)%aggr,stat=info) - ! Further intermediates, if any + medparms = prec%precv(iszv-1)%parms + call save_smoothers(prec%precv(iszv-1),med_sm,med_sm2,info) do i=iszv, nplevs - 1 if (info == 0) tprecv(i)%parms = medparms if (info == 0) call restore_smoothers(tprecv(i),med_sm,med_sm2,info) @@ -302,11 +303,12 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info) ! Build the mapping between levels i-1 and i and the matrix ! at level i ! + if (do_timings) call psb_tic(idx_bldtp) if (info == psb_success_)& & call prec%precv(i)%bld_tprol(prec%precv(i-1)%base_a,& & prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,prec%ag_data,info) - + if (do_timings) call psb_toc(idx_bldtp) if (info /= psb_success_) then call psb_errpush(psb_err_internal_error_,name,& & a_err='Map build') @@ -387,20 +389,23 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info) nlaggr = prec%precv(newsz)%map%naggr call prec%precv(newsz)%tprol%clone(op_prol,info) end if - + if (do_timings) call psb_tic(idx_matasb) if (info == psb_success_) call prec%precv(newsz)%mat_asb( & & prec%precv(newsz-1)%base_a,prec%precv(newsz-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) + if (do_timings) call psb_toc(idx_matasb) if (info /= 0) then call psb_errpush(psb_err_internal_error_,name,& & a_err='Mat asb') goto 9999 endif exit array_build_loop - else + else + if (do_timings) call psb_tic(idx_matasb) if (info == psb_success_) call prec%precv(i)%mat_asb(& & prec%precv(i-1)%base_a,prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) + if (do_timings) call psb_toc(idx_matasb) end if if (info /= psb_success_) then call psb_errpush(psb_err_internal_error_,name,& diff --git a/mlprec/impl/mld_z_hierarchy_bld.f90 b/mlprec/impl/mld_z_hierarchy_bld.f90 index 087c50e5..c295efdc 100644 --- a/mlprec/impl/mld_z_hierarchy_bld.f90 +++ b/mlprec/impl/mld_z_hierarchy_bld.f90 @@ -83,15 +83,17 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info) & nplevs, mxplevs integer(psb_lpk_) :: iaggsize, casize real(psb_dpk_) :: mnaggratio, sizeratio, athresh, aomega - class(mld_z_base_smoother_type), allocatable :: coarse_sm, base_sm, med_sm, & - & base_sm2, med_sm2, coarse_sm2 + class(mld_z_base_smoother_type), allocatable :: coarse_sm, med_sm, & + & med_sm2, coarse_sm2 class(mld_z_base_aggregator_type), allocatable :: tmp_aggr - type(mld_dml_parms) :: baseparms, medparms, coarseparms + type(mld_dml_parms) :: medparms, coarseparms integer(psb_lpk_), allocatable :: ilaggr(:), nlaggr(:) type(psb_lzspmat_type) :: op_prol type(mld_z_onelev_type), allocatable :: tprecv(:) integer(psb_ipk_) :: debug_level, debug_unit character(len=20) :: name, ch_err + integer(psb_ipk_), save :: idx_bldtp=-1, idx_matasb=-1 + logical, parameter :: do_timings=.false. info=psb_success_ err=0 @@ -110,6 +112,10 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info) if (debug_level >= psb_debug_outer_) & & write(debug_unit,*) me,' ',trim(name),& & 'Entering ' + if ((do_timings).and.(idx_bldtp==-1)) & + & idx_bldtp = psb_get_timer_idx("BLD_HIER: bld_tprol") + if ((do_timings).and.(idx_matasb==-1)) & + & idx_matasb = psb_get_timer_idx("BLD_HIER: mmat_asb") ! if (.not.allocated(prec%precv)) then @@ -207,15 +213,12 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info) end if nplevs = max(itwo,mxplevs) + ! + ! The coarse parameters will be needed later + ! coarseparms = prec%precv(iszv)%parms - baseparms = prec%precv(1)%parms - medparms = prec%precv(2)%parms - call save_smoothers(prec%precv(iszv),coarse_sm,coarse_sm2,info) - if (info == 0) call save_smoothers(prec%precv(2),med_sm,med_sm2,info) - if (info == 0) call save_smoothers(prec%precv(1),base_sm,base_sm2,info) if (info /= psb_success_) then - write(0,*) 'Error in saving smoothers',info call psb_errpush(psb_err_internal_error_,name,a_err='Base level precbuild.') goto 9999 end if @@ -225,19 +228,17 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info) if (iszv /= nplevs) then allocate(tprecv(nplevs),stat=info) ! First all existing levels - if (info == 0) tprecv(1)%parms = baseparms - if (info == 0) call restore_smoothers(tprecv(1),& - & prec%precv(1)%sm,prec%precv(1)%sm2a,info) - if (info == 0) call move_alloc(prec%precv(1)%aggr,tprecv(1)%aggr) - do i=2, min(iszv,nplevs) - 1 - if (info == 0) tprecv(i)%parms = medparms + do i=1, min(iszv,nplevs) - 1 + if (info == 0) tprecv(i)%parms = prec%precv(i)%parms if (info == 0) call restore_smoothers(tprecv(i),& & prec%precv(i)%sm,prec%precv(i)%sm2a,info) if (info == 0) call move_alloc(prec%precv(i)%aggr,tprecv(i)%aggr) end do if (iszv < nplevs) then + ! Further intermediates, if needed allocate(tmp_aggr,source=tprecv(iszv-1)%aggr,stat=info) - ! Further intermediates, if any + medparms = prec%precv(iszv-1)%parms + call save_smoothers(prec%precv(iszv-1),med_sm,med_sm2,info) do i=iszv, nplevs - 1 if (info == 0) tprecv(i)%parms = medparms if (info == 0) call restore_smoothers(tprecv(i),med_sm,med_sm2,info) @@ -302,11 +303,12 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info) ! Build the mapping between levels i-1 and i and the matrix ! at level i ! + if (do_timings) call psb_tic(idx_bldtp) if (info == psb_success_)& & call prec%precv(i)%bld_tprol(prec%precv(i-1)%base_a,& & prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,prec%ag_data,info) - + if (do_timings) call psb_toc(idx_bldtp) if (info /= psb_success_) then call psb_errpush(psb_err_internal_error_,name,& & a_err='Map build') @@ -387,20 +389,23 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info) nlaggr = prec%precv(newsz)%map%naggr call prec%precv(newsz)%tprol%clone(op_prol,info) end if - + if (do_timings) call psb_tic(idx_matasb) if (info == psb_success_) call prec%precv(newsz)%mat_asb( & & prec%precv(newsz-1)%base_a,prec%precv(newsz-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) + if (do_timings) call psb_toc(idx_matasb) if (info /= 0) then call psb_errpush(psb_err_internal_error_,name,& & a_err='Mat asb') goto 9999 endif exit array_build_loop - else + else + if (do_timings) call psb_tic(idx_matasb) if (info == psb_success_) call prec%precv(i)%mat_asb(& & prec%precv(i-1)%base_a,prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) + if (do_timings) call psb_toc(idx_matasb) end if if (info /= psb_success_) then call psb_errpush(psb_err_internal_error_,name,& From fa4623f54b20a626692db621d714e58734818084 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Wed, 22 Apr 2020 10:41:08 +0100 Subject: [PATCH 07/11] Ensure using correct NZ value --- mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 | 3 ++- mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 | 3 ++- mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 | 3 ++- mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 | 3 ++- 4 files changed, 8 insertions(+), 4 deletions(-) diff --git a/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 index 0e75eb30..deea748f 100644 --- a/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 @@ -170,10 +170,11 @@ subroutine mld_c_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& call csr_restr%free() call acsr3%free() call ac_csr%mv_to_lcoo(ac_coo,info) - call ac_coo%fix(info) nza = ac_coo%get_nzeros() if (debug) write(0,*) me,trim(name),' Fixing ac ',& & ac_coo%get_nrows(),ac_coo%get_ncols(), nza + call ac_coo%fix(info) + nza = ac_coo%get_nzeros() call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) call ac_coo%set_nrows(ntaggr) diff --git a/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 index 0d85c647..ecde7398 100644 --- a/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 @@ -170,10 +170,11 @@ subroutine mld_d_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& call csr_restr%free() call acsr3%free() call ac_csr%mv_to_lcoo(ac_coo,info) - call ac_coo%fix(info) nza = ac_coo%get_nzeros() if (debug) write(0,*) me,trim(name),' Fixing ac ',& & ac_coo%get_nrows(),ac_coo%get_ncols(), nza + call ac_coo%fix(info) + nza = ac_coo%get_nzeros() call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) call ac_coo%set_nrows(ntaggr) diff --git a/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 index 4ae68bbb..a2c2d1d0 100644 --- a/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 @@ -170,10 +170,11 @@ subroutine mld_s_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& call csr_restr%free() call acsr3%free() call ac_csr%mv_to_lcoo(ac_coo,info) - call ac_coo%fix(info) nza = ac_coo%get_nzeros() if (debug) write(0,*) me,trim(name),' Fixing ac ',& & ac_coo%get_nrows(),ac_coo%get_ncols(), nza + call ac_coo%fix(info) + nza = ac_coo%get_nzeros() call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) call ac_coo%set_nrows(ntaggr) diff --git a/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 index 98aa63f2..b0c459d5 100644 --- a/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 @@ -170,10 +170,11 @@ subroutine mld_z_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& call csr_restr%free() call acsr3%free() call ac_csr%mv_to_lcoo(ac_coo,info) - call ac_coo%fix(info) nza = ac_coo%get_nzeros() if (debug) write(0,*) me,trim(name),' Fixing ac ',& & ac_coo%get_nrows(),ac_coo%get_ncols(), nza + call ac_coo%fix(info) + nza = ac_coo%get_nzeros() call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) call ac_coo%set_nrows(ntaggr) From cb0e72698091774c92363c1b9db31645afb8a880 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Wed, 22 Apr 2020 11:53:50 +0200 Subject: [PATCH 08/11] New call ac_coo%fix --- mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 | 5 ++--- mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 | 5 ++--- mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 | 5 ++--- mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 | 5 ++--- 4 files changed, 8 insertions(+), 12 deletions(-) diff --git a/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 index deea748f..1e912368 100644 --- a/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_c_spmm_bld_inner.f90 @@ -170,11 +170,10 @@ subroutine mld_c_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& call csr_restr%free() call acsr3%free() call ac_csr%mv_to_lcoo(ac_coo,info) - nza = ac_coo%get_nzeros() - if (debug) write(0,*) me,trim(name),' Fixing ac ',& - & ac_coo%get_nrows(),ac_coo%get_ncols(), nza call ac_coo%fix(info) nza = ac_coo%get_nzeros() + if (debug) write(0,*) me,trim(name),' Fixed ac ',& + & ac_coo%get_nrows(),ac_coo%get_ncols(), nza call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) call ac_coo%set_nrows(ntaggr) diff --git a/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 index ecde7398..ddeed79b 100644 --- a/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_d_spmm_bld_inner.f90 @@ -170,11 +170,10 @@ subroutine mld_d_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& call csr_restr%free() call acsr3%free() call ac_csr%mv_to_lcoo(ac_coo,info) - nza = ac_coo%get_nzeros() - if (debug) write(0,*) me,trim(name),' Fixing ac ',& - & ac_coo%get_nrows(),ac_coo%get_ncols(), nza call ac_coo%fix(info) nza = ac_coo%get_nzeros() + if (debug) write(0,*) me,trim(name),' Fixed ac ',& + & ac_coo%get_nrows(),ac_coo%get_ncols(), nza call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) call ac_coo%set_nrows(ntaggr) diff --git a/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 index a2c2d1d0..0ae800d5 100644 --- a/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_s_spmm_bld_inner.f90 @@ -170,11 +170,10 @@ subroutine mld_s_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& call csr_restr%free() call acsr3%free() call ac_csr%mv_to_lcoo(ac_coo,info) - nza = ac_coo%get_nzeros() - if (debug) write(0,*) me,trim(name),' Fixing ac ',& - & ac_coo%get_nrows(),ac_coo%get_ncols(), nza call ac_coo%fix(info) nza = ac_coo%get_nzeros() + if (debug) write(0,*) me,trim(name),' Fixed ac ',& + & ac_coo%get_nrows(),ac_coo%get_ncols(), nza call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) call ac_coo%set_nrows(ntaggr) diff --git a/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 b/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 index b0c459d5..65eaf1a3 100644 --- a/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 +++ b/mlprec/impl/aggregator/mld_z_spmm_bld_inner.f90 @@ -170,11 +170,10 @@ subroutine mld_z_spmm_bld_inner(a_csr,desc_a,nlaggr,parms,ac,& call csr_restr%free() call acsr3%free() call ac_csr%mv_to_lcoo(ac_coo,info) - nza = ac_coo%get_nzeros() - if (debug) write(0,*) me,trim(name),' Fixing ac ',& - & ac_coo%get_nrows(),ac_coo%get_ncols(), nza call ac_coo%fix(info) nza = ac_coo%get_nzeros() + if (debug) write(0,*) me,trim(name),' Fixed ac ',& + & ac_coo%get_nrows(),ac_coo%get_ncols(), nza call desc_cprol%indxmap%l2gip(ac_coo%ia(1:nza),info) call desc_cprol%indxmap%l2gip(ac_coo%ja(1:nza),info) call ac_coo%set_nrows(ntaggr) From 6fb0172cd723de7f5b47b5675ba547981b1d739c Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Wed, 22 Apr 2020 17:39:57 +0100 Subject: [PATCH 09/11] Update support for SuperLU_Dist version 6 --- config/pac.m4 | 89 ++++++++++++++----- configure | 139 ++++++++++++++++++++++++++---- mlprec/impl/mld_dslud_interface.c | 49 +++++++++-- mlprec/impl/mld_zslud_interface.c | 49 +++++++++-- 4 files changed, 277 insertions(+), 49 deletions(-) diff --git a/config/pac.m4 b/config/pac.m4 index 896847b8..0de702d7 100644 --- a/config/pac.m4 +++ b/config/pac.m4 @@ -692,9 +692,19 @@ AC_CHECK_HEADERS([slu_ddefs.h], [pac_slu_header_ok=yes], [pac_slu_header_ok=no; SLU_INCLUDES=""]) if test "x$pac_slu_header_ok" == "xno" ; then -dnl Maybe Include or include subdirs? +dnl Maybe include subdirs? + unset ac_cv_header_slu_ddefs_h + SLU_INCLUDES="-I$mld2p4_cv_superludir/include " + CPPFLAGS="$SLU_INCLUDES $save_CPPFLAGS" + + AC_CHECK_HEADERS([slu_ddefs.h], + [pac_slu_header_ok=yes], + [pac_slu_header_ok=no; SLU_INCLUDES=""]) +fi +if test "x$pac_slu_header_ok" == "xno" ; then +dnl Maybe Include subdirs? unset ac_cv_header_slu_ddefs_h - SLU_INCLUDES="-I$mld2p4_cv_superludir/include -I$mld2p4_cv_superludir/Include " + SLU_INCLUDES="-I$mld2p4_cv_superludir/Include " CPPFLAGS="$SLU_INCLUDES $save_CPPFLAGS" AC_CHECK_HEADERS([slu_ddefs.h], @@ -715,7 +725,7 @@ if test "x$pac_slu_header_ok" == "xyes" ; then LIBS="$SLU_LIBS -lm $save_LIBS"; AC_TRY_LINK_FUNC(superlu_malloc, [mld2p4_cv_have_superlu=yes;pac_slu_lib_ok=yes;], - [mld2p4_cv_have_superlu=no;pac_slu_lib_ok=no; SLU_LIBS="";]) + [mld2p4_cv_have_superlu=no;pac_slu_lib_ok=no; SLU_LIBS=""; ]) fi if test "x$pac_slu_lib_ok" == "xno" ; then dnl Maybe lib64? @@ -807,9 +817,19 @@ AC_CHECK_HEADERS([superlu_ddefs.h], [pac_sludist_header_ok=yes], [pac_sludist_header_ok=no; SLUDIST_INCLUDES=""]) if test "x$pac_sludist_header_ok" == "xno" ; then -dnl Maybe Include or include subdirs? +dnl Maybe include subdirs? + unset ac_cv_header_superlu_ddefs_h + SLUDIST_INCLUDES="-I$mld2p4_cv_superludistdir/include" + CPPFLAGS="$SLUDIST_INCLUDES $save_CPPFLAGS" + + AC_CHECK_HEADERS([superlu_ddefs.h], + [pac_sludist_header_ok=yes], + [pac_sludist_header_ok=no; SLUDIST_INCLUDES=""; SLUDIST_LIBS=""; ]) +fi +if test "x$pac_sludist_header_ok" == "xno" ; then +dnl Maybe Include subdirs? unset ac_cv_header_superlu_ddefs_h - SLUDIST_INCLUDES="-I$mld2p4_cv_superludistdir/include -I$mld2p4_cv_superludistdir/Include" + SLUDIST_INCLUDES="-I$mld2p4_cv_superludistdir/Include" CPPFLAGS="$SLUDIST_INCLUDES $save_CPPFLAGS" AC_CHECK_HEADERS([superlu_ddefs.h], @@ -829,18 +849,42 @@ if test "x$pac_sludist_header_ok" == "xyes" ; then dnl Maybe lib? SLUDIST_LIBS="$mld2p4_cv_superludist -L$mld2p4_cv_superludistdir/lib"; LIBS="$SLUDIST_LIBS -lm $save_LIBS"; + AC_TRY_LINK_FUNC(superlu_malloc_dist, + [mld2p4_cv_have_superludist=yes;pac_sludist_lib_ok=yes;], + [mld2p4_cv_have_superludist=no;pac_sludist_lib_ok=no; + SLUDIST_LIBS="";]) + fi + if test "x$pac_sludist_lib_ok" == "xno" ; then + dnl Maybe lib64? + SLUDIST_LIBS="$mld2p4_cv_superludist -L$mld2p4_cv_superludistdir/lib64"; + LIBS="$SLUDIST_LIBS -lm $save_LIBS"; AC_TRY_LINK_FUNC(superlu_malloc_dist, [mld2p4_cv_have_superludist=yes;pac_sludist_lib_ok=yes;], [mld2p4_cv_have_superludist=no;pac_sludist_lib_ok=no; SLUDIST_LIBS="";SLUDIST_INCLUDES=""]) - fi + fi AC_MSG_RESULT($pac_sludist_lib_ok) if test "x$pac_sludist_lib_ok" == "xyes" ; then - AC_MSG_CHECKING([for superlu_dist version 4]) - AC_LANG_PUSH([C]) - ac_cc=${MPICC-$CC} - AC_COMPILE_IFELSE( - [AC_LANG_SOURCE([[ #include "superlu_ddefs.h" + AC_MSG_CHECKING([for superlu_dist version 6]) + AC_LANG_PUSH([C]) + ac_cc=${MPICC-$CC} + AC_COMPILE_IFELSE( + [AC_LANG_SOURCE([[ #include "superlu_ddefs.h" + int testdslud() + { dLUstruct_t *LUstruct; + int n; + dLUstructInit(n, LUstruct); + }]])], + [ AC_MSG_RESULT([yes]); pac_sludist_version="6";], + [ AC_MSG_RESULT([no]); pac_sludist_version="";]) + AC_LANG_POP([C]) + if test "x$pac_sludist_version" == "x" ; then + + AC_MSG_CHECKING([for superlu_dist version 4]) + AC_LANG_PUSH([C]) + ac_cc=${MPICC-$CC} + AC_COMPILE_IFELSE( + [AC_LANG_SOURCE([[ #include "superlu_ddefs.h" int testdslud() { LUstruct_t *LUstruct; int n; @@ -850,11 +894,11 @@ if test "x$pac_sludist_header_ok" == "xyes" ; then [ AC_MSG_RESULT([no]); pac_sludist_version="3";]) AC_LANG_POP([C]) if test "x$pac_sludist_version" == "x4" ; then - AC_MSG_CHECKING([for superlu_dist version 5]) - AC_LANG_PUSH([C]) - ac_cc=${MPICC-$CC} - AC_COMPILE_IFELSE( - [AC_LANG_SOURCE([[ #include "superlu_ddefs.h" + AC_MSG_CHECKING([for superlu_dist version 5]) + AC_LANG_PUSH([C]) + ac_cc=${MPICC-$CC} + AC_COMPILE_IFELSE( + [AC_LANG_SOURCE([[ #include "superlu_ddefs.h" int testdslud() { superlu_dist_options_t options; int n; @@ -862,14 +906,15 @@ if test "x$pac_sludist_header_ok" == "xyes" ; then }]])], [ AC_MSG_RESULT([yes]); pac_sludist_version="5";], [ AC_MSG_RESULT([no]); pac_sludist_version="4";]) - AC_LANG_POP([C]) + AC_LANG_POP([C]) fi - else - SLUDIST_LIBS=""; - SLUDIST_INCLUDES=""; - fi - fi + fi + else + SLUDIST_LIBS=""; + SLUDIST_INCLUDES=""; + fi +fi LIBS="$save_LIBS"; CPPFLAGS="$save_CPPFLAGS"; diff --git a/configure b/configure index 7f9f0b05..8504a18e 100755 --- a/configure +++ b/configure @@ -8637,7 +8637,27 @@ done if test "x$pac_slu_header_ok" == "xno" ; then unset ac_cv_header_slu_ddefs_h - SLU_INCLUDES="-I$mld2p4_cv_superludir/include -I$mld2p4_cv_superludir/Include " + SLU_INCLUDES="-I$mld2p4_cv_superludir/include " + CPPFLAGS="$SLU_INCLUDES $save_CPPFLAGS" + + for ac_header in slu_ddefs.h +do : + ac_fn_c_check_header_mongrel "$LINENO" "slu_ddefs.h" "ac_cv_header_slu_ddefs_h" "$ac_includes_default" +if test "x$ac_cv_header_slu_ddefs_h" = xyes; then : + cat >>confdefs.h <<_ACEOF +#define HAVE_SLU_DDEFS_H 1 +_ACEOF + pac_slu_header_ok=yes +else + pac_slu_header_ok=no; SLU_INCLUDES="" +fi + +done + +fi +if test "x$pac_slu_header_ok" == "xno" ; then + unset ac_cv_header_slu_ddefs_h + SLU_INCLUDES="-I$mld2p4_cv_superludir/Include " CPPFLAGS="$SLU_INCLUDES $save_CPPFLAGS" for ac_header in slu_ddefs.h @@ -8881,7 +8901,27 @@ done if test "x$pac_sludist_header_ok" == "xno" ; then unset ac_cv_header_superlu_ddefs_h - SLUDIST_INCLUDES="-I$mld2p4_cv_superludistdir/include -I$mld2p4_cv_superludistdir/Include" + SLUDIST_INCLUDES="-I$mld2p4_cv_superludistdir/include" + CPPFLAGS="$SLUDIST_INCLUDES $save_CPPFLAGS" + + for ac_header in superlu_ddefs.h +do : + ac_fn_c_check_header_mongrel "$LINENO" "superlu_ddefs.h" "ac_cv_header_superlu_ddefs_h" "$ac_includes_default" +if test "x$ac_cv_header_superlu_ddefs_h" = xyes; then : + cat >>confdefs.h <<_ACEOF +#define HAVE_SUPERLU_DDEFS_H 1 +_ACEOF + pac_sludist_header_ok=yes +else + pac_sludist_header_ok=no; SLUDIST_INCLUDES=""; SLUDIST_LIBS=""; +fi + +done + +fi +if test "x$pac_sludist_header_ok" == "xno" ; then + unset ac_cv_header_superlu_ddefs_h + SLUDIST_INCLUDES="-I$mld2p4_cv_superludistdir/Include" CPPFLAGS="$SLUDIST_INCLUDES $save_CPPFLAGS" for ac_header in superlu_ddefs.h @@ -8937,6 +8977,36 @@ rm -f core conftest.err conftest.$ac_objext \ cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ +/* Override any GCC internal prototype to avoid an error. + Use char because int might match the return type of a GCC + builtin and then its argument prototype would still apply. */ +#ifdef __cplusplus +extern "C" +#endif +char superlu_malloc_dist (); +int +main () +{ +return superlu_malloc_dist (); + ; + return 0; +} +_ACEOF +if ac_fn_c_try_link "$LINENO"; then : + mld2p4_cv_have_superludist=yes;pac_sludist_lib_ok=yes; +else + mld2p4_cv_have_superludist=no;pac_sludist_lib_ok=no; + SLUDIST_LIBS=""; +fi +rm -f core conftest.err conftest.$ac_objext \ + conftest$ac_exeext conftest.$ac_ext + fi + if test "x$pac_sludist_lib_ok" == "xno" ; then + SLUDIST_LIBS="$mld2p4_cv_superludist -L$mld2p4_cv_superludistdir/lib64"; + LIBS="$SLUDIST_LIBS -lm $save_LIBS"; + cat confdefs.h - <<_ACEOF >conftest.$ac_ext +/* end confdefs.h. */ + /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ @@ -8960,20 +9030,54 @@ else fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext - fi + fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $pac_sludist_lib_ok" >&5 $as_echo "$pac_sludist_lib_ok" >&6; } if test "x$pac_sludist_lib_ok" == "xyes" ; then - { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 4" >&5 + { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 6" >&5 +$as_echo_n "checking for superlu_dist version 6... " >&6; } + ac_ext=c +ac_cpp='$CPP $CPPFLAGS' +ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' +ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' +ac_compiler_gnu=$ac_cv_c_compiler_gnu + + ac_cc=${MPICC-$CC} + cat confdefs.h - <<_ACEOF >conftest.$ac_ext +/* end confdefs.h. */ + #include "superlu_ddefs.h" + int testdslud() + { dLUstruct_t *LUstruct; + int n; + dLUstructInit(n, LUstruct); + } +_ACEOF +if ac_fn_c_try_compile "$LINENO"; then : + { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 +$as_echo "yes" >&6; }; pac_sludist_version="6"; +else + { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 +$as_echo "no" >&6; }; pac_sludist_version=""; +fi +rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext + ac_ext=c +ac_cpp='$CPP $CPPFLAGS' +ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' +ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' +ac_compiler_gnu=$ac_cv_c_compiler_gnu + + if test "x$pac_sludist_version" == "x" ; then + + { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 4" >&5 $as_echo_n "checking for superlu_dist version 4... " >&6; } - ac_ext=c + ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu - ac_cc=${MPICC-$CC} - cat confdefs.h - <<_ACEOF >conftest.$ac_ext + ac_cc=${MPICC-$CC} + cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include "superlu_ddefs.h" int testdslud() @@ -8997,16 +9101,16 @@ ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $ ac_compiler_gnu=$ac_cv_c_compiler_gnu if test "x$pac_sludist_version" == "x4" ; then - { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 5" >&5 + { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 5" >&5 $as_echo_n "checking for superlu_dist version 5... " >&6; } - ac_ext=c + ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu - ac_cc=${MPICC-$CC} - cat confdefs.h - <<_ACEOF >conftest.$ac_ext + ac_cc=${MPICC-$CC} + cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include "superlu_ddefs.h" int testdslud() @@ -9023,7 +9127,7 @@ else $as_echo "no" >&6; }; pac_sludist_version="4"; fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext - ac_ext=c + ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' @@ -9031,11 +9135,12 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu fi - else - SLUDIST_LIBS=""; - SLUDIST_INCLUDES=""; - fi - fi + fi + else + SLUDIST_LIBS=""; + SLUDIST_INCLUDES=""; + fi +fi LIBS="$save_LIBS"; CPPFLAGS="$save_CPPFLAGS"; diff --git a/mlprec/impl/mld_dslud_interface.c b/mlprec/impl/mld_dslud_interface.c index 8c784ebf..6d2bfcfc 100644 --- a/mlprec/impl/mld_dslud_interface.c +++ b/mlprec/impl/mld_dslud_interface.c @@ -94,13 +94,21 @@ SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. #define HANDLE_SIZE 8 +#if defined(SLUD_VERSION_6) +typedef struct { + SuperMatrix *A; + dLUstruct_t *LUstruct; + gridinfo_t *grid; + dScalePermstruct_t *ScalePermstruct; +} factors_t; +#else typedef struct { SuperMatrix *A; LUstruct_t *LUstruct; gridinfo_t *grid; ScalePermstruct_t *ScalePermstruct; } factors_t; - +#endif #else @@ -127,14 +135,20 @@ int mld_dsludist_fact(int n, int nl, int nnzl, int ffstr, SuperMatrix *A; NRformat_loc *Astore; +#if defined(SLUD_VERSION_6) + dScalePermstruct_t *ScalePermstruct; + dLUstruct_t *LUstruct; + dSOLVEstruct_t SOLVEstruct; +#else ScalePermstruct_t *ScalePermstruct; LUstruct_t *LUstruct; SOLVEstruct_t SOLVEstruct; +#endif gridinfo_t *grid; int i, panel_size, permc_spec, relax, info; trans_t trans; double drop_tol = 0.0, b[1], berr[1]; -#if defined(SLUD_VERSION_5) +#if defined(SLUD_VERSION_6)||defined(SLUD_VERSION_5) superlu_dist_options_t options; #elif defined(SLUD_VERSION_4)||defined(SLUD_VERSION_3) superlu_options_t options; @@ -160,10 +174,18 @@ int mld_dsludist_fact(int n, int nl, int nnzl, int ffstr, SLU_NR_loc, SLU_D, SLU_GE); /* Initialize ScalePermstruct and LUstruct. */ +#if defined(SLUD_VERSION_6) + ScalePermstruct = (dScalePermstruct_t *) SUPERLU_MALLOC(sizeof(dScalePermstruct_t)); + LUstruct = (dLUstruct_t *) SUPERLU_MALLOC(sizeof(dLUstruct_t)); + dScalePermstructInit(n,n, ScalePermstruct); +#else ScalePermstruct = (ScalePermstruct_t *) SUPERLU_MALLOC(sizeof(ScalePermstruct_t)); LUstruct = (LUstruct_t *) SUPERLU_MALLOC(sizeof(LUstruct_t)); ScalePermstructInit(n,n, ScalePermstruct); -#if defined(SLUD_VERSION_4) || defined(SLUD_VERSION_5) +#endif +#if defined(SLUD_VERSION_6) + dLUstructInit(n, LUstruct); +#elif defined(SLUD_VERSION_4) || defined(SLUD_VERSION_5) LUstructInit(n, LUstruct); #elif defined(SLUD_VERSION_3) LUstructInit(n,n, LUstruct); @@ -223,15 +245,21 @@ int mld_dsludist_solve(int itrans, int n, int nrhs, */ #ifdef Have_SLUDist_ SuperMatrix *A; +#if defined(SLUD_VERSION_6) + dScalePermstruct_t *ScalePermstruct; + dLUstruct_t *LUstruct; + dSOLVEstruct_t SOLVEstruct; +#else ScalePermstruct_t *ScalePermstruct; LUstruct_t *LUstruct; SOLVEstruct_t SOLVEstruct; +#endif gridinfo_t *grid; int i, panel_size, permc_spec, relax, info; trans_t trans; double drop_tol = 0.0; double *berr; -#if defined(SLUD_VERSION_5) +#if defined(SLUD_VERSION_6)||defined(SLUD_VERSION_5) superlu_dist_options_t options; #elif defined(SLUD_VERSION_4)||defined(SLUD_VERSION_3) superlu_options_t options; @@ -303,15 +331,21 @@ int mld_dsludist_free(void *f_factors) */ #ifdef Have_SLUDist_ SuperMatrix *A; +#if defined(SLUD_VERSION_6) + dScalePermstruct_t *ScalePermstruct; + dLUstruct_t *LUstruct; + dSOLVEstruct_t SOLVEstruct; +#else ScalePermstruct_t *ScalePermstruct; LUstruct_t *LUstruct; SOLVEstruct_t SOLVEstruct; +#endif gridinfo_t *grid; int i, panel_size, permc_spec, relax; trans_t trans; double drop_tol = 0.0; double *berr; -#if defined(SLUD_VERSION_5) +#if defined(SLUD_VERSION_6)||defined(SLUD_VERSION_5) superlu_dist_options_t options; #elif defined(SLUD_VERSION_4)||defined(SLUD_VERSION_3) superlu_options_t options; @@ -334,8 +368,13 @@ int mld_dsludist_free(void *f_factors) // we either have a leak or a segfault here. // To be investigated further. //Destroy_CompRowLoc_Matrix_dist(A); +#if defined(SLUD_VERSION_6) + dScalePermstructFree(ScalePermstruct); + dLUstructFree(LUstruct); +#else ScalePermstructFree(ScalePermstruct); LUstructFree(LUstruct); +#endif superlu_gridexit(grid); free(grid); diff --git a/mlprec/impl/mld_zslud_interface.c b/mlprec/impl/mld_zslud_interface.c index ca2ae963..9a51d5c4 100644 --- a/mlprec/impl/mld_zslud_interface.c +++ b/mlprec/impl/mld_zslud_interface.c @@ -92,13 +92,21 @@ SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. #define HANDLE_SIZE 8 +#if defined(SLUD_VERSION_6) +typedef struct { + SuperMatrix *A; + zLUstruct_t *LUstruct; + gridinfo_t *grid; + zScalePermstruct_t *ScalePermstruct; +} factors_t; +#else typedef struct { SuperMatrix *A; LUstruct_t *LUstruct; gridinfo_t *grid; ScalePermstruct_t *ScalePermstruct; } factors_t; - +#endif #else @@ -132,14 +140,20 @@ int mld_zsludist_fact(int n, int nl, int nnzl, int ffstr, SuperMatrix *A; NRformat_loc *Astore; +#if defined(SLUD_VERSION_6) + zScalePermstruct_t *ScalePermstruct; + zLUstruct_t *LUstruct; + zSOLVEstruct_t SOLVEstruct; +#else ScalePermstruct_t *ScalePermstruct; LUstruct_t *LUstruct; SOLVEstruct_t SOLVEstruct; +#endif gridinfo_t *grid; int i, panel_size, permc_spec, relax, info; trans_t trans; double drop_tol = 0.0,berr[1]; -#if defined(SLUD_VERSION_5) +#if defined(SLUD_VERSION_6)||defined(SLUD_VERSION_5) superlu_dist_options_t options; #elif defined(SLUD_VERSION_4)||defined(SLUD_VERSION_3) superlu_options_t options; @@ -165,10 +179,18 @@ int mld_zsludist_fact(int n, int nl, int nnzl, int ffstr, SLU_NR_loc, SLU_Z, SLU_GE); /* Initialize ScalePermstruct and LUstruct. */ +#if defined(SLUD_VERSION_6) + ScalePermstruct = (zScalePermstruct_t *) SUPERLU_MALLOC(sizeof(zScalePermstruct_t)); + LUstruct = (zLUstruct_t *) SUPERLU_MALLOC(sizeof(zLUstruct_t)); + zScalePermstructInit(n,n, ScalePermstruct); +#else ScalePermstruct = (ScalePermstruct_t *) SUPERLU_MALLOC(sizeof(ScalePermstruct_t)); LUstruct = (LUstruct_t *) SUPERLU_MALLOC(sizeof(LUstruct_t)); ScalePermstructInit(n,n, ScalePermstruct); -#if defined(SLUD_VERSION_4) || defined(SLUD_VERSION_5) +#endif +#if defined(SLUD_VERSION_6) + zLUstructInit(n, LUstruct); +#elif defined(SLUD_VERSION_4) || defined(SLUD_VERSION_5) LUstructInit(n, LUstruct); #elif defined(SLUD_VERSION_3) LUstructInit(n,n, LUstruct); @@ -233,15 +255,21 @@ int mld_zsludist_solve(int itrans, int n, int nrhs, */ #ifdef Have_SLUDist_ SuperMatrix *A; +#if defined(SLUD_VERSION_6) + zScalePermstruct_t *ScalePermstruct; + zLUstruct_t *LUstruct; + zSOLVEstruct_t SOLVEstruct; +#else ScalePermstruct_t *ScalePermstruct; LUstruct_t *LUstruct; SOLVEstruct_t SOLVEstruct; +#endif gridinfo_t *grid; int i, panel_size, permc_spec, relax, info; trans_t trans; double drop_tol = 0.0; double *berr; -#if defined(SLUD_VERSION_5) +#if defined(SLUD_VERSION_6)||defined(SLUD_VERSION_5) superlu_dist_options_t options; #elif defined(SLUD_VERSION_4)||defined(SLUD_VERSION_3) superlu_options_t options; @@ -313,15 +341,21 @@ int mld_zsludist_free(void *f_factors) */ #ifdef Have_SLUDist_ SuperMatrix *A; +#if defined(SLUD_VERSION_6) + zScalePermstruct_t *ScalePermstruct; + zLUstruct_t *LUstruct; + zSOLVEstruct_t SOLVEstruct; +#else ScalePermstruct_t *ScalePermstruct; LUstruct_t *LUstruct; SOLVEstruct_t SOLVEstruct; +#endif gridinfo_t *grid; int i, panel_size, permc_spec, relax; trans_t trans; double drop_tol = 0.0; double *berr; -#if defined(SLUD_VERSION_5) +#if defined(SLUD_VERSION_6)||defined(SLUD_VERSION_5) superlu_dist_options_t options; #elif defined(SLUD_VERSION_4)||defined(SLUD_VERSION_3) superlu_options_t options; @@ -344,8 +378,13 @@ int mld_zsludist_free(void *f_factors) // we either have a leak or a segfault here. // To be investigated further. //Destroy_CompRowLoc_Matrix_dist(A); +#if defined(SLUD_VERSION_6) + zScalePermstructFree(ScalePermstruct); + zLUstructFree(LUstruct); +#else ScalePermstructFree(ScalePermstruct); LUstructFree(LUstruct); +#endif superlu_gridexit(grid); free(grid); From 2f1d6e29bb8b3da5947b79358c16ce06301a7533 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 24 Apr 2020 16:02:16 +0200 Subject: [PATCH 10/11] Fixes for interfacing with multiple versions of SuperLU_DIST --- config/pac.m4 | 148 +++++++--- configure | 439 ++++++++++++++++++++++-------- configure.ac | 23 +- mlprec/impl/mld_dslud_interface.c | 51 +++- mlprec/impl/mld_zslud_interface.c | 57 +++- 5 files changed, 537 insertions(+), 181 deletions(-) diff --git a/config/pac.m4 b/config/pac.m4 index 896847b8..9837c14a 100644 --- a/config/pac.m4 +++ b/config/pac.m4 @@ -417,27 +417,30 @@ dnl ac_link='${MPIFC-$FC} -o conftest${ac_exeext} $FCFLAGS $LDFLAGS conftest.$ac ac_link='${MPIFC-$FC} -o conftest${ac_exeext} $FCFLAGS conftest.$ac_ext $LDFLAGS $LIBS 1>&5' dnl Warning : square brackets are EVIL! -AC_LINK_IFELSE([ +AC_LINK_IFELSE( + [AC_LANG_SOURCE([[ program test use psb_base_mod, only : psb_version_major_ print *,psb_version_major_ - end program test], + end program test]])], [pac_cv_psblas_major=`./conftest${ac_exeext} | sed 's/^ *//'`], [pac_cv_psblas_major="unknown"]) -AC_LINK_IFELSE([ +AC_LINK_IFELSE( + [AC_LANG_SOURCE([[ program test use psb_base_mod, only : psb_version_minor_ print *,psb_version_minor_ - end program test], + end program test]])], [pac_cv_psblas_minor=`./conftest${ac_exeext} | sed 's/^ *//'`], [pac_cv_psblas_minor="unknown"]) -AC_LINK_IFELSE([ +AC_LINK_IFELSE( + [AC_LANG_SOURCE([[ program test use psb_base_mod, only : psb_patchlevel_ print *,psb_patchlevel_ - end program test], + end program test]])], [pac_cv_psblas_patchlevel=`./conftest${ac_exeext} | sed 's/^ *//'`], [pac_cv_psblas_patchlevel="unknown"]) LDFLAGS="$save_LDFLAGS"; @@ -692,9 +695,19 @@ AC_CHECK_HEADERS([slu_ddefs.h], [pac_slu_header_ok=yes], [pac_slu_header_ok=no; SLU_INCLUDES=""]) if test "x$pac_slu_header_ok" == "xno" ; then -dnl Maybe Include or include subdirs? +dnl Maybe include subdirs? unset ac_cv_header_slu_ddefs_h - SLU_INCLUDES="-I$mld2p4_cv_superludir/include -I$mld2p4_cv_superludir/Include " + SLU_INCLUDES="-I$mld2p4_cv_superludir/include " + CPPFLAGS="$SLU_INCLUDES $save_CPPFLAGS" + + AC_CHECK_HEADERS([slu_ddefs.h], + [pac_slu_header_ok=yes], + [pac_slu_header_ok=no; SLU_INCLUDES=""]) +fi +if test "x$pac_slu_header_ok" == "xno" ; then +dnl Maybe Include subdirs? + unset ac_cv_header_slu_ddefs_h + SLU_INCLUDES="-I$mld2p4_cv_superludir/Include " CPPFLAGS="$SLU_INCLUDES $save_CPPFLAGS" AC_CHECK_HEADERS([slu_ddefs.h], @@ -807,9 +820,19 @@ AC_CHECK_HEADERS([superlu_ddefs.h], [pac_sludist_header_ok=yes], [pac_sludist_header_ok=no; SLUDIST_INCLUDES=""]) if test "x$pac_sludist_header_ok" == "xno" ; then -dnl Maybe Include or include subdirs? +dnl Maybe include subdirs? + unset ac_cv_header_superlu_ddefs_h + SLUDIST_INCLUDES="-I$mld2p4_cv_superludistdir/include" + CPPFLAGS="$SLUDIST_INCLUDES $save_CPPFLAGS" + + AC_CHECK_HEADERS([superlu_ddefs.h], + [pac_sludist_header_ok=yes], + [pac_sludist_header_ok=no; SLUDIST_INCLUDES=""; SLUDIST_LIBS=""; ]) +fi +if test "x$pac_sludist_header_ok" == "xno" ; then +dnl Maybe Include subdirs? unset ac_cv_header_superlu_ddefs_h - SLUDIST_INCLUDES="-I$mld2p4_cv_superludistdir/include -I$mld2p4_cv_superludistdir/Include" + SLUDIST_INCLUDES="-I$mld2p4_cv_superludistdir/Include" CPPFLAGS="$SLUDIST_INCLUDES $save_CPPFLAGS" AC_CHECK_HEADERS([superlu_ddefs.h], @@ -829,52 +852,91 @@ if test "x$pac_sludist_header_ok" == "xyes" ; then dnl Maybe lib? SLUDIST_LIBS="$mld2p4_cv_superludist -L$mld2p4_cv_superludistdir/lib"; LIBS="$SLUDIST_LIBS -lm $save_LIBS"; + AC_TRY_LINK_FUNC(superlu_malloc_dist, + [mld2p4_cv_have_superludist=yes;pac_sludist_lib_ok=yes;], + [mld2p4_cv_have_superludist=no;pac_sludist_lib_ok=no; + SLUDIST_LIBS="";]) + fi + if test "x$pac_sludist_lib_ok" == "xno" ; then + dnl Maybe lib64? + SLUDIST_LIBS="$mld2p4_cv_superludist -L$mld2p4_cv_superludistdir/lib64"; + LIBS="$SLUDIST_LIBS -lm $save_LIBS"; AC_TRY_LINK_FUNC(superlu_malloc_dist, [mld2p4_cv_have_superludist=yes;pac_sludist_lib_ok=yes;], [mld2p4_cv_have_superludist=no;pac_sludist_lib_ok=no; SLUDIST_LIBS="";SLUDIST_INCLUDES=""]) - fi - AC_MSG_RESULT($pac_sludist_lib_ok) - if test "x$pac_sludist_lib_ok" == "xyes" ; then - AC_MSG_CHECKING([for superlu_dist version 4]) - AC_LANG_PUSH([C]) - ac_cc=${MPICC-$CC} - AC_COMPILE_IFELSE( - [AC_LANG_SOURCE([[ #include "superlu_ddefs.h" + fi + AC_MSG_RESULT($pac_sludist_lib_ok) +fi + +if test "x$pac_sludist_lib_ok" == "xyes" ; then + + AC_LANG_PUSH([C]) + ac_cc=${MPICC-$CC} + ac_exeext=""; + CPPFLAGS="$SLUDIST_INCLUDES $save_CPPFLAGS" + LIBS="$SLUDIST_LIBS -lm $save_LIBS"; + AC_LINK_IFELSE( + [AC_LANG_SOURCE([[#include + #include + + void main() + { int i=SUPERLU_DIST_MAJOR_VERSION; + printf("%d\n",i); + } ]])], + [mld2p4_cv_superludist_major=`./conftest${ac_exeext} | sed 's/^ *//'`], + [mld2p4_cv_superludist_major="unknown"]) + AC_LINK_IFELSE( + [AC_LANG_SOURCE([[#include + #include + + void main() + { int i=SUPERLU_DIST_MINOR_VERSION; + printf("%d\n",i); + }]])], + [mld2p4_cv_superludist_minor=`./conftest${ac_exeext} | sed 's/^ *//'`], + [mld2p4_cv_superludist_minor="unknown"]) + AC_LANG_POP([C]) + if test "x$mld2p4_cv_superludist_major" == "xunknown" ; then + AC_MSG_CHECKING([for superlu_dist version 4]) + AC_LANG_PUSH([C]) + ac_cc=${MPICC-$CC} + AC_COMPILE_IFELSE( + [AC_LANG_SOURCE([[ #include "superlu_ddefs.h" int testdslud() { LUstruct_t *LUstruct; int n; LUstructInit(n, LUstruct); }]])], - [ AC_MSG_RESULT([yes]); pac_sludist_version="4";], - [ AC_MSG_RESULT([no]); pac_sludist_version="3";]) - AC_LANG_POP([C]) - if test "x$pac_sludist_version" == "x4" ; then - AC_MSG_CHECKING([for superlu_dist version 5]) - AC_LANG_PUSH([C]) - ac_cc=${MPICC-$CC} - AC_COMPILE_IFELSE( - [AC_LANG_SOURCE([[ #include "superlu_ddefs.h" - int testdslud() - { superlu_dist_options_t options; - int n; - set_default_options_dist(&options); - }]])], - [ AC_MSG_RESULT([yes]); pac_sludist_version="5";], - [ AC_MSG_RESULT([no]); pac_sludist_version="4";]) - AC_LANG_POP([C]) - + [ AC_MSG_RESULT([yes]); mld2p4_cv_superludist_major="4"; mld2p4_cv_superludist_minor="";], + [ AC_MSG_RESULT([no]); mld2p4_cv_superludist_major="3"; mld2p4_cv_superludist_minor="";]) + AC_LANG_POP([C]) + if test "x$mld2p4_cv_superludist_major" == "x4" ; then + AC_MSG_CHECKING([for superlu_dist version 5]) + AC_LANG_PUSH([C]) + ac_cc=${MPICC-$CC} + AC_COMPILE_IFELSE( + [AC_LANG_SOURCE([[ #include "superlu_ddefs.h" + int testdslud() + { superlu_dist_options_t options; + int n; + set_default_options_dist(&options); + }]])], + [ AC_MSG_RESULT([yes]); mld2p4_cv_superludist_major="5"; mld2p4_cv_superludist_minor="";], + [ AC_MSG_RESULT([no]); mld2p4_cv_superludist_major="4"; mld2p4_cv_superludist_minor="";]) + AC_LANG_POP([C]) + fi fi - else - SLUDIST_LIBS=""; - SLUDIST_INCLUDES=""; - fi - fi - + AC_MSG_NOTICE([SuperLU_dist version $mld2p4_cv_superludist_major.$mld2p4_cv_superludist_minor.]) + + else + SLUDIST_LIBS=""; + SLUDIST_INCLUDES=""; + fi LIBS="$save_LIBS"; CPPFLAGS="$save_CPPFLAGS"; CC="$save_CC"; -AC_LANG_POP([C]) + AC_LANG_POP([C]) ])dnl dnl @synopsis PAC_CHECK_MUMPS diff --git a/configure b/configure index 7f9f0b05..47514f7a 100755 --- a/configure +++ b/configure @@ -666,7 +666,6 @@ am__nodep AMDEPBACKSLASH AMDEP_FALSE AMDEP_TRUE -am__quote am__include DEPDIR ac_ct_CC @@ -743,7 +742,8 @@ PACKAGE_VERSION PACKAGE_TARNAME PACKAGE_NAME PATH_SEPARATOR -SHELL' +SHELL +am__quote' ac_subst_files='' ac_user_opts=' enable_option_checking @@ -2665,7 +2665,7 @@ fi { $as_echo "$as_me:${as_lineno-$LINENO}: Loaded $pac_cv_status_file $FC $MPIFC $BLACS_LIBS" >&5 $as_echo "$as_me: Loaded $pac_cv_status_file $FC $MPIFC $BLACS_LIBS" >&6;} -am__api_version='1.13' +am__api_version='1.16' ac_aux_dir= for ac_dir in "$srcdir" "$srcdir/.." "$srcdir/../.."; do @@ -2866,8 +2866,8 @@ test "$program_suffix" != NONE && ac_script='s/[\\$]/&&/g;s/;s,x,x,$//' program_transform_name=`$as_echo "$program_transform_name" | sed "$ac_script"` -# expand $ac_aux_dir to an absolute path -am_aux_dir=`cd $ac_aux_dir && pwd` +# Expand $ac_aux_dir to an absolute path. +am_aux_dir=`cd "$ac_aux_dir" && pwd` if test x"${MISSING+set}" != xset; then case $am_aux_dir in @@ -2886,7 +2886,7 @@ else $as_echo "$as_me: WARNING: 'missing' script is too old or missing" >&2;} fi -if test x"${install_sh}" != xset; then +if test x"${install_sh+set}" != xset; then case $am_aux_dir in *\ * | *\ *) install_sh="\${SHELL} '$am_aux_dir/install-sh'" ;; @@ -3210,12 +3210,12 @@ MAKEINFO=${MAKEINFO-"${am_missing_run}makeinfo"} # For better backward compatibility. To be removed once Automake 1.9.x # dies out for good. For more background, see: -# -# +# +# mkdir_p='$(MKDIR_P)' -# We need awk for the "check" target. The system "awk" is bad on -# some platforms. +# We need awk for the "check" target (and possibly the TAP driver). The +# system "awk" is bad on some platforms. # Always define AMTAR for backward compatibility. Yes, it's still used # in the wild :-( We should find a proper way to deprecate it ... AMTAR='$${TAR-tar}' @@ -3231,6 +3231,48 @@ am__tar='$${TAR-tar} chof - "$$tardir"' am__untar='$${TAR-tar} xf -' +# POSIX will say in a future version that running "rm -f" with no argument +# is OK; and we want to be able to make that assumption in our Makefile +# recipes. So use an aggressive probe to check that the usage we want is +# actually supported "in the wild" to an acceptable degree. +# See automake bug#10828. +# To make any issue more visible, cause the running configure to be aborted +# by default if the 'rm' program in use doesn't match our expectations; the +# user can still override this though. +if rm -f && rm -fr && rm -rf; then : OK; else + cat >&2 <<'END' +Oops! + +Your 'rm' program seems unable to run without file operands specified +on the command line, even when the '-f' option is present. This is contrary +to the behaviour of most rm programs out there, and not conforming with +the upcoming POSIX standard: + +Please tell bug-automake@gnu.org about your system, including the value +of your $PATH and any error possibly output before this message. This +can help us improve future automake versions. + +END + if test x"$ACCEPT_INFERIOR_RM_PROGRAM" = x"yes"; then + echo 'Configuration will proceed anyway, since you have set the' >&2 + echo 'ACCEPT_INFERIOR_RM_PROGRAM variable to "yes"' >&2 + echo >&2 + else + cat >&2 <<'END' +Aborting the configuration process, to ensure you take notice of the issue. + +You can download and install GNU coreutils to get an 'rm' implementation +that behaves properly: . + +If you want to complete the configuration process using your problematic +'rm' anyway, export the environment variable ACCEPT_INFERIOR_RM_PROGRAM +to "yes", and re-run configure. + +END + as_fn_error $? "Your 'rm' program is bad, sorry." "$LINENO" 5 + fi +fi + # # Installation. @@ -4056,49 +4098,108 @@ ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu + +ac_ext=c +ac_cpp='$CPP $CPPFLAGS' +ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' +ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' +ac_compiler_gnu=$ac_cv_c_compiler_gnu +{ $as_echo "$as_me:${as_lineno-$LINENO}: checking whether $CC understands -c and -o together" >&5 +$as_echo_n "checking whether $CC understands -c and -o together... " >&6; } +if ${am_cv_prog_cc_c_o+:} false; then : + $as_echo_n "(cached) " >&6 +else + cat confdefs.h - <<_ACEOF >conftest.$ac_ext +/* end confdefs.h. */ + +int +main () +{ + + ; + return 0; +} +_ACEOF + # Make sure it works both with $CC and with simple cc. + # Following AC_PROG_CC_C_O, we do the test twice because some + # compilers refuse to overwrite an existing .o file with -o, + # though they will create one. + am_cv_prog_cc_c_o=yes + for am_i in 1 2; do + if { echo "$as_me:$LINENO: $CC -c conftest.$ac_ext -o conftest2.$ac_objext" >&5 + ($CC -c conftest.$ac_ext -o conftest2.$ac_objext) >&5 2>&5 + ac_status=$? + echo "$as_me:$LINENO: \$? = $ac_status" >&5 + (exit $ac_status); } \ + && test -f conftest2.$ac_objext; then + : OK + else + am_cv_prog_cc_c_o=no + break + fi + done + rm -f core conftest* + unset am_i +fi +{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $am_cv_prog_cc_c_o" >&5 +$as_echo "$am_cv_prog_cc_c_o" >&6; } +if test "$am_cv_prog_cc_c_o" != yes; then + # Losing compiler, so override with the script. + # FIXME: It is wrong to rewrite CC. + # But if we don't then we get into trouble of one sort or another. + # A longer-term fix would be to have automake use am__CC in this case, + # and then we could set am__CC="\$(top_srcdir)/compile \$(CC)" + CC="$am_aux_dir/compile $CC" +fi +ac_ext=c +ac_cpp='$CPP $CPPFLAGS' +ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' +ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' +ac_compiler_gnu=$ac_cv_c_compiler_gnu + DEPDIR="${am__leading_dot}deps" ac_config_commands="$ac_config_commands depfiles" - -am_make=${MAKE-make} -cat > confinc << 'END' +{ $as_echo "$as_me:${as_lineno-$LINENO}: checking whether ${MAKE-make} supports the include directive" >&5 +$as_echo_n "checking whether ${MAKE-make} supports the include directive... " >&6; } +cat > confinc.mk << 'END' am__doit: - @echo this is the am__doit target + @echo this is the am__doit target >confinc.out .PHONY: am__doit END -# If we don't find an include directive, just comment out the code. -{ $as_echo "$as_me:${as_lineno-$LINENO}: checking for style of include used by $am_make" >&5 -$as_echo_n "checking for style of include used by $am_make... " >&6; } am__include="#" am__quote= -_am_result=none -# First try GNU make style include. -echo "include confinc" > confmf -# Ignore all kinds of additional output from 'make'. -case `$am_make -s -f confmf 2> /dev/null` in #( -*the\ am__doit\ target*) - am__include=include - am__quote= - _am_result=GNU - ;; -esac -# Now try BSD make style include. -if test "$am__include" = "#"; then - echo '.include "confinc"' > confmf - case `$am_make -s -f confmf 2> /dev/null` in #( - *the\ am__doit\ target*) - am__include=.include - am__quote="\"" - _am_result=BSD +# BSD make does it like this. +echo '.include "confinc.mk" # ignored' > confmf.BSD +# Other make implementations (GNU, Solaris 10, AIX) do it like this. +echo 'include confinc.mk # ignored' > confmf.GNU +_am_result=no +for s in GNU BSD; do + { echo "$as_me:$LINENO: ${MAKE-make} -f confmf.$s && cat confinc.out" >&5 + (${MAKE-make} -f confmf.$s && cat confinc.out) >&5 2>&5 + ac_status=$? + echo "$as_me:$LINENO: \$? = $ac_status" >&5 + (exit $ac_status); } + case $?:`cat confinc.out 2>/dev/null` in #( + '0:this is the am__doit target') : + case $s in #( + BSD) : + am__include='.include' am__quote='"' ;; #( + *) : + am__include='include' am__quote='' ;; +esac ;; #( + *) : ;; - esac -fi - - -{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $_am_result" >&5 -$as_echo "$_am_result" >&6; } -rm -f confinc confmf +esac + if test "$am__include" != "#"; then + _am_result="yes ($s style)" + break + fi +done +rm -f confinc.* confmf.* +{ $as_echo "$as_me:${as_lineno-$LINENO}: result: ${_am_result}" >&5 +$as_echo "${_am_result}" >&6; } # Check whether --enable-dependency-tracking was given. if test "${enable_dependency_tracking+set}" = set; then : @@ -8637,7 +8738,27 @@ done if test "x$pac_slu_header_ok" == "xno" ; then unset ac_cv_header_slu_ddefs_h - SLU_INCLUDES="-I$mld2p4_cv_superludir/include -I$mld2p4_cv_superludir/Include " + SLU_INCLUDES="-I$mld2p4_cv_superludir/include " + CPPFLAGS="$SLU_INCLUDES $save_CPPFLAGS" + + for ac_header in slu_ddefs.h +do : + ac_fn_c_check_header_mongrel "$LINENO" "slu_ddefs.h" "ac_cv_header_slu_ddefs_h" "$ac_includes_default" +if test "x$ac_cv_header_slu_ddefs_h" = xyes; then : + cat >>confdefs.h <<_ACEOF +#define HAVE_SLU_DDEFS_H 1 +_ACEOF + pac_slu_header_ok=yes +else + pac_slu_header_ok=no; SLU_INCLUDES="" +fi + +done + +fi +if test "x$pac_slu_header_ok" == "xno" ; then + unset ac_cv_header_slu_ddefs_h + SLU_INCLUDES="-I$mld2p4_cv_superludir/Include " CPPFLAGS="$SLU_INCLUDES $save_CPPFLAGS" for ac_header in slu_ddefs.h @@ -8881,7 +9002,27 @@ done if test "x$pac_sludist_header_ok" == "xno" ; then unset ac_cv_header_superlu_ddefs_h - SLUDIST_INCLUDES="-I$mld2p4_cv_superludistdir/include -I$mld2p4_cv_superludistdir/Include" + SLUDIST_INCLUDES="-I$mld2p4_cv_superludistdir/include" + CPPFLAGS="$SLUDIST_INCLUDES $save_CPPFLAGS" + + for ac_header in superlu_ddefs.h +do : + ac_fn_c_check_header_mongrel "$LINENO" "superlu_ddefs.h" "ac_cv_header_superlu_ddefs_h" "$ac_includes_default" +if test "x$ac_cv_header_superlu_ddefs_h" = xyes; then : + cat >>confdefs.h <<_ACEOF +#define HAVE_SUPERLU_DDEFS_H 1 +_ACEOF + pac_sludist_header_ok=yes +else + pac_sludist_header_ok=no; SLUDIST_INCLUDES=""; SLUDIST_LIBS=""; +fi + +done + +fi +if test "x$pac_sludist_header_ok" == "xno" ; then + unset ac_cv_header_superlu_ddefs_h + SLUDIST_INCLUDES="-I$mld2p4_cv_superludistdir/Include" CPPFLAGS="$SLUDIST_INCLUDES $save_CPPFLAGS" for ac_header in superlu_ddefs.h @@ -8937,6 +9078,36 @@ rm -f core conftest.err conftest.$ac_objext \ cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ +/* Override any GCC internal prototype to avoid an error. + Use char because int might match the return type of a GCC + builtin and then its argument prototype would still apply. */ +#ifdef __cplusplus +extern "C" +#endif +char superlu_malloc_dist (); +int +main () +{ +return superlu_malloc_dist (); + ; + return 0; +} +_ACEOF +if ac_fn_c_try_link "$LINENO"; then : + mld2p4_cv_have_superludist=yes;pac_sludist_lib_ok=yes; +else + mld2p4_cv_have_superludist=no;pac_sludist_lib_ok=no; + SLUDIST_LIBS=""; +fi +rm -f core conftest.err conftest.$ac_objext \ + conftest$ac_exeext conftest.$ac_ext + fi + if test "x$pac_sludist_lib_ok" == "xno" ; then + SLUDIST_LIBS="$mld2p4_cv_superludist -L$mld2p4_cv_superludistdir/lib64"; + LIBS="$SLUDIST_LIBS -lm $save_LIBS"; + cat confdefs.h - <<_ACEOF >conftest.$ac_ext +/* end confdefs.h. */ + /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ @@ -8960,20 +9131,54 @@ else fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext - fi + fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $pac_sludist_lib_ok" >&5 $as_echo "$pac_sludist_lib_ok" >&6; } if test "x$pac_sludist_lib_ok" == "xyes" ; then - { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 4" >&5 + { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 6" >&5 +$as_echo_n "checking for superlu_dist version 6... " >&6; } + ac_ext=c +ac_cpp='$CPP $CPPFLAGS' +ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' +ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' +ac_compiler_gnu=$ac_cv_c_compiler_gnu + + ac_cc=${MPICC-$CC} + cat confdefs.h - <<_ACEOF >conftest.$ac_ext +/* end confdefs.h. */ + #include "superlu_ddefs.h" + int testdslud() + { dLUstruct_t *LUstruct; + int n; + dLUstructInit(n, LUstruct); + } +_ACEOF +if ac_fn_c_try_compile "$LINENO"; then : + { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 +$as_echo "yes" >&6; }; pac_sludist_version="6"; +else + { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 +$as_echo "no" >&6; }; pac_sludist_version=""; +fi +rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext + ac_ext=c +ac_cpp='$CPP $CPPFLAGS' +ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' +ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' +ac_compiler_gnu=$ac_cv_c_compiler_gnu + + if test "x$pac_sludist_version" == "x" ; then + + { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 4" >&5 $as_echo_n "checking for superlu_dist version 4... " >&6; } - ac_ext=c + ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu - ac_cc=${MPICC-$CC} - cat confdefs.h - <<_ACEOF >conftest.$ac_ext + ac_cc=${MPICC-$CC} + cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include "superlu_ddefs.h" int testdslud() @@ -8997,16 +9202,16 @@ ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $ ac_compiler_gnu=$ac_cv_c_compiler_gnu if test "x$pac_sludist_version" == "x4" ; then - { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 5" >&5 + { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 5" >&5 $as_echo_n "checking for superlu_dist version 5... " >&6; } - ac_ext=c + ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu - ac_cc=${MPICC-$CC} - cat confdefs.h - <<_ACEOF >conftest.$ac_ext + ac_cc=${MPICC-$CC} + cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include "superlu_ddefs.h" int testdslud() @@ -9023,7 +9228,7 @@ else $as_echo "no" >&6; }; pac_sludist_version="4"; fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext - ac_ext=c + ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' @@ -9031,11 +9236,12 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu fi - else - SLUDIST_LIBS=""; - SLUDIST_INCLUDES=""; - fi - fi + fi + else + SLUDIST_LIBS=""; + SLUDIST_INCLUDES=""; + fi +fi LIBS="$save_LIBS"; CPPFLAGS="$save_CPPFLAGS"; @@ -9878,7 +10084,7 @@ cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 # # INIT-COMMANDS # -AMDEP_TRUE="$AMDEP_TRUE" ac_aux_dir="$ac_aux_dir" +AMDEP_TRUE="$AMDEP_TRUE" MAKE="${MAKE-make}" _ACEOF @@ -10323,29 +10529,35 @@ $as_echo "$as_me: executing $ac_file commands" >&6;} # Older Autoconf quotes --file arguments for eval, but not when files # are listed without --file. Let's play safe and only enable the eval # if we detect the quoting. - case $CONFIG_FILES in - *\'*) eval set x "$CONFIG_FILES" ;; - *) set x $CONFIG_FILES ;; - esac + # TODO: see whether this extra hack can be removed once we start + # requiring Autoconf 2.70 or later. + case $CONFIG_FILES in #( + *\'*) : + eval set x "$CONFIG_FILES" ;; #( + *) : + set x $CONFIG_FILES ;; #( + *) : + ;; +esac shift - for mf + # Used to flag and report bootstrapping failures. + am_rc=0 + for am_mf do # Strip MF so we end up with the name of the file. - mf=`echo "$mf" | sed -e 's/:.*$//'` - # Check whether this is an Automake generated Makefile or not. - # We used to match only the files named 'Makefile.in', but - # some people rename them; so instead we look at the file content. - # Grep'ing the first line is not enough: some people post-process - # each Makefile.in and add a new line on top of each file to say so. - # Grep'ing the whole file is not good either: AIX grep has a line + am_mf=`$as_echo "$am_mf" | sed -e 's/:.*$//'` + # Check whether this is an Automake generated Makefile which includes + # dependency-tracking related rules and includes. + # Grep'ing the whole file directly is not great: AIX grep has a line # limit of 2048, but all sed's we know have understand at least 4000. - if sed -n 's,^#.*generated by automake.*,X,p' "$mf" | grep X >/dev/null 2>&1; then - dirpart=`$as_dirname -- "$mf" || -$as_expr X"$mf" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ - X"$mf" : 'X\(//\)[^/]' \| \ - X"$mf" : 'X\(//\)$' \| \ - X"$mf" : 'X\(/\)' \| . 2>/dev/null || -$as_echo X"$mf" | + sed -n 's,^am--depfiles:.*,X,p' "$am_mf" | grep X >/dev/null 2>&1 \ + || continue + am_dirpart=`$as_dirname -- "$am_mf" || +$as_expr X"$am_mf" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ + X"$am_mf" : 'X\(//\)[^/]' \| \ + X"$am_mf" : 'X\(//\)$' \| \ + X"$am_mf" : 'X\(/\)' \| . 2>/dev/null || +$as_echo X"$am_mf" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q @@ -10363,53 +10575,48 @@ $as_echo X"$mf" | q } s/.*/./; q'` - else - continue - fi - # Extract the definition of DEPDIR, am__include, and am__quote - # from the Makefile without running 'make'. - DEPDIR=`sed -n 's/^DEPDIR = //p' < "$mf"` - test -z "$DEPDIR" && continue - am__include=`sed -n 's/^am__include = //p' < "$mf"` - test -z "$am__include" && continue - am__quote=`sed -n 's/^am__quote = //p' < "$mf"` - # Find all dependency output files, they are included files with - # $(DEPDIR) in their names. We invoke sed twice because it is the - # simplest approach to changing $(DEPDIR) to its actual value in the - # expansion. - for file in `sed -n " - s/^$am__include $am__quote\(.*(DEPDIR).*\)$am__quote"'$/\1/p' <"$mf" | \ - sed -e 's/\$(DEPDIR)/'"$DEPDIR"'/g'`; do - # Make sure the directory exists. - test -f "$dirpart/$file" && continue - fdir=`$as_dirname -- "$file" || -$as_expr X"$file" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ - X"$file" : 'X\(//\)[^/]' \| \ - X"$file" : 'X\(//\)$' \| \ - X"$file" : 'X\(/\)' \| . 2>/dev/null || -$as_echo X"$file" | - sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ - s//\1/ - q - } - /^X\(\/\/\)[^/].*/{ + am_filepart=`$as_basename -- "$am_mf" || +$as_expr X/"$am_mf" : '.*/\([^/][^/]*\)/*$' \| \ + X"$am_mf" : 'X\(//\)$' \| \ + X"$am_mf" : 'X\(/\)' \| . 2>/dev/null || +$as_echo X/"$am_mf" | + sed '/^.*\/\([^/][^/]*\)\/*$/{ s//\1/ q } - /^X\(\/\/\)$/{ + /^X\/\(\/\/\)$/{ s//\1/ q } - /^X\(\/\).*/{ + /^X\/\(\/\).*/{ s//\1/ q } s/.*/./; q'` - as_dir=$dirpart/$fdir; as_fn_mkdir_p - # echo "creating $dirpart/$file" - echo '# dummy' > "$dirpart/$file" - done + { echo "$as_me:$LINENO: cd "$am_dirpart" \ + && sed -e '/# am--include-marker/d' "$am_filepart" \ + | $MAKE -f - am--depfiles" >&5 + (cd "$am_dirpart" \ + && sed -e '/# am--include-marker/d' "$am_filepart" \ + | $MAKE -f - am--depfiles) >&5 2>&5 + ac_status=$? + echo "$as_me:$LINENO: \$? = $ac_status" >&5 + (exit $ac_status); } || am_rc=$? done + if test $am_rc -ne 0; then + { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 +$as_echo "$as_me: error: in \`$ac_pwd':" >&2;} +as_fn_error $? "Something went wrong bootstrapping makefile fragments + for automatic dependency tracking. Try re-running configure with the + '--disable-dependency-tracking' option to at least be able to build + the package (albeit without support for automatic dependency tracking). +See \`config.log' for more details" "$LINENO" 5; } + fi + { am_dirpart=; unset am_dirpart;} + { am_filepart=; unset am_filepart;} + { am_mf=; unset am_mf;} + { am_rc=; unset am_rc;} + rm -f conftest-deps.mk } ;; diff --git a/configure.ac b/configure.ac index 969daaa3..5fbf3480 100755 --- a/configure.ac +++ b/configure.ac @@ -34,11 +34,11 @@ dnl NOTE : odd configurations like ifc + gcc still await in the mist of the unkn ############################################################################### # NOTE: the literal for version (the second argument to AC_INIT should be a literal!) -AC_INIT([MLD2P4],2.1.1, [https://github.com/sfilippone/mld2p4-2/issues]) +AC_INIT([MLD2P4],2.3.1, [https://github.com/sfilippone/mld2p4-2/issues]) # VERSION is the file containing the PSBLAS version code # FIXME -mld2p4_cv_version="2.1.1" +mld2p4_cv_version="2.3.1" # A sample source file AC_CONFIG_SRCDIR([mlprec/mld_prec_type.f90]) @@ -680,8 +680,15 @@ else SLU_FLAGS="" fi -PAC_CHECK_SUPERLUDIST -if test "x$mld2p4_cv_have_superludist" == "xyes" ; then +PAC_CHECK_SUPERLUDIST() + +if test "x$mld2p4_cv_have_superludist" == "xyes" ; then + pac_sludist_version="$mld2p4_cv_superludist_major"; + if (($mld2p4_cv_superludist_major==6)); then + if (($mld2p4_cv_superludist_minor>=3)); then + pac_sludist_version="63"; + fi + fi SLUDIST_FLAGS="" SLUDIST_FLAGS="-DHave_SLUDist_ -DSLUD_VERSION_$pac_sludist_version $SLUDIST_INCLUDES" FDEFINES="$mld_cv_define_prepend-DHAVE_SLUDIST_ $FDEFINES" @@ -789,10 +796,10 @@ AC_MSG_NOTICE([ ${PACKAGE_NAME} ${mld2p4_cv_version} has been configured as follows: PSBLAS library : ${PSBLAS_DIR} - MUMPS : ${mld2p4_cv_have_mumps} - SuperLU : ${mld2p4_cv_have_superlu} - SuperLU_Dist : ${mld2p4_cv_have_superludist} - UMFPack : ${mld2p4_cv_have_umfpack} + MUMPS detected : ${mld2p4_cv_have_mumps} + SuperLU detected : ${mld2p4_cv_have_superlu} + SuperLU_Dist detected : ${mld2p4_cv_have_superludist} + UMFPack detected : ${mld2p4_cv_have_umfpack} If you are satisfied, run 'make' to build ${PACKAGE_NAME} and its documentation; otherwise type ./configure --help=short for a complete list of configure options specific to ${PACKAGE_NAME}. diff --git a/mlprec/impl/mld_dslud_interface.c b/mlprec/impl/mld_dslud_interface.c index 8c784ebf..754cd521 100644 --- a/mlprec/impl/mld_dslud_interface.c +++ b/mlprec/impl/mld_dslud_interface.c @@ -94,13 +94,21 @@ SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. #define HANDLE_SIZE 8 +#if defined(SLUD_VERSION_63) +typedef struct { + SuperMatrix *A; + dLUstruct_t *LUstruct; + gridinfo_t *grid; + dScalePermstruct_t *ScalePermstruct; +} factors_t; +#else typedef struct { SuperMatrix *A; LUstruct_t *LUstruct; gridinfo_t *grid; ScalePermstruct_t *ScalePermstruct; } factors_t; - +#endif #else @@ -127,14 +135,20 @@ int mld_dsludist_fact(int n, int nl, int nnzl, int ffstr, SuperMatrix *A; NRformat_loc *Astore; +#if defined(SLUD_VERSION_63) + dScalePermstruct_t *ScalePermstruct; + dLUstruct_t *LUstruct; + dSOLVEstruct_t SOLVEstruct; +#else ScalePermstruct_t *ScalePermstruct; LUstruct_t *LUstruct; SOLVEstruct_t SOLVEstruct; +#endif gridinfo_t *grid; int i, panel_size, permc_spec, relax, info; trans_t trans; double drop_tol = 0.0, b[1], berr[1]; -#if defined(SLUD_VERSION_5) +#if defined(SLUD_VERSION_63) || defined(SLUD_VERSION_6)||defined(SLUD_VERSION_5) superlu_dist_options_t options; #elif defined(SLUD_VERSION_4)||defined(SLUD_VERSION_3) superlu_options_t options; @@ -160,10 +174,18 @@ int mld_dsludist_fact(int n, int nl, int nnzl, int ffstr, SLU_NR_loc, SLU_D, SLU_GE); /* Initialize ScalePermstruct and LUstruct. */ +#if defined(SLUD_VERSION_63) + ScalePermstruct = (dScalePermstruct_t *) SUPERLU_MALLOC(sizeof(dScalePermstruct_t)); + LUstruct = (dLUstruct_t *) SUPERLU_MALLOC(sizeof(dLUstruct_t)); + dScalePermstructInit(n,n, ScalePermstruct); +#else ScalePermstruct = (ScalePermstruct_t *) SUPERLU_MALLOC(sizeof(ScalePermstruct_t)); LUstruct = (LUstruct_t *) SUPERLU_MALLOC(sizeof(LUstruct_t)); ScalePermstructInit(n,n, ScalePermstruct); -#if defined(SLUD_VERSION_4) || defined(SLUD_VERSION_5) +#endif +#if defined(SLUD_VERSION_63) + dLUstructInit(n, LUstruct); +#elif defined(SLUD_VERSION_4) || defined(SLUD_VERSION_5) || defined(SLUD_VERSION_6) LUstructInit(n, LUstruct); #elif defined(SLUD_VERSION_3) LUstructInit(n,n, LUstruct); @@ -223,17 +245,23 @@ int mld_dsludist_solve(int itrans, int n, int nrhs, */ #ifdef Have_SLUDist_ SuperMatrix *A; +#if defined(SLUD_VERSION_63) + dScalePermstruct_t *ScalePermstruct; + dLUstruct_t *LUstruct; + dSOLVEstruct_t SOLVEstruct; +#else ScalePermstruct_t *ScalePermstruct; LUstruct_t *LUstruct; SOLVEstruct_t SOLVEstruct; +#endif gridinfo_t *grid; int i, panel_size, permc_spec, relax, info; trans_t trans; double drop_tol = 0.0; double *berr; -#if defined(SLUD_VERSION_5) +#if defined(SLUD_VERSION_63) || defined(SLUD_VERSION_6) ||defined(SLUD_VERSION_5) superlu_dist_options_t options; -#elif defined(SLUD_VERSION_4)||defined(SLUD_VERSION_3) +#elif defined(SLUD_VERSION_4)|| defined(SLUD_VERSION_3) superlu_options_t options; #else choke_on_me; @@ -303,15 +331,21 @@ int mld_dsludist_free(void *f_factors) */ #ifdef Have_SLUDist_ SuperMatrix *A; +#if defined(SLUD_VERSION_63) + dScalePermstruct_t *ScalePermstruct; + dLUstruct_t *LUstruct; + dSOLVEstruct_t SOLVEstruct; +#else ScalePermstruct_t *ScalePermstruct; LUstruct_t *LUstruct; SOLVEstruct_t SOLVEstruct; +#endif gridinfo_t *grid; int i, panel_size, permc_spec, relax; trans_t trans; double drop_tol = 0.0; double *berr; -#if defined(SLUD_VERSION_5) +#if defined(SLUD_VERSION_63)||defined(SLUD_VERSION_6)||defined(SLUD_VERSION_5) superlu_dist_options_t options; #elif defined(SLUD_VERSION_4)||defined(SLUD_VERSION_3) superlu_options_t options; @@ -334,8 +368,13 @@ int mld_dsludist_free(void *f_factors) // we either have a leak or a segfault here. // To be investigated further. //Destroy_CompRowLoc_Matrix_dist(A); +#if defined(SLUD_VERSION_63) + dScalePermstructFree(ScalePermstruct); + dLUstructFree(LUstruct); +#else ScalePermstructFree(ScalePermstruct); LUstructFree(LUstruct); +#endif superlu_gridexit(grid); free(grid); diff --git a/mlprec/impl/mld_zslud_interface.c b/mlprec/impl/mld_zslud_interface.c index ca2ae963..8db9d899 100644 --- a/mlprec/impl/mld_zslud_interface.c +++ b/mlprec/impl/mld_zslud_interface.c @@ -5,8 +5,10 @@ * based on PSBLAS (Parallel Sparse BLAS version 3.5) * * (C) Copyright 2008-2018 - * - * Salvatore Filippone + * + * Salvatore Filippone + * Ambra Abdullahi Hassan + * Alfredo Buttari CNRS-IRIT, Toulouse, FR * Pasqua D'Ambra * Daniela di Serafino * @@ -92,13 +94,21 @@ SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. #define HANDLE_SIZE 8 +#if defined(SLUD_VERSION_63) +typedef struct { + SuperMatrix *A; + zLUstruct_t *LUstruct; + gridinfo_t *grid; + zScalePermstruct_t *ScalePermstruct; +} factors_t; +#else typedef struct { SuperMatrix *A; LUstruct_t *LUstruct; gridinfo_t *grid; ScalePermstruct_t *ScalePermstruct; } factors_t; - +#endif #else @@ -132,14 +142,20 @@ int mld_zsludist_fact(int n, int nl, int nnzl, int ffstr, SuperMatrix *A; NRformat_loc *Astore; +#if defined(SLUD_VERSION_63) + zScalePermstruct_t *ScalePermstruct; + zLUstruct_t *LUstruct; + zSOLVEstruct_t SOLVEstruct; +#else ScalePermstruct_t *ScalePermstruct; LUstruct_t *LUstruct; SOLVEstruct_t SOLVEstruct; +#endif gridinfo_t *grid; int i, panel_size, permc_spec, relax, info; trans_t trans; double drop_tol = 0.0,berr[1]; -#if defined(SLUD_VERSION_5) +#if defined(SLUD_VERSION_63) || defined(SLUD_VERSION_6)||defined(SLUD_VERSION_5) superlu_dist_options_t options; #elif defined(SLUD_VERSION_4)||defined(SLUD_VERSION_3) superlu_options_t options; @@ -165,10 +181,18 @@ int mld_zsludist_fact(int n, int nl, int nnzl, int ffstr, SLU_NR_loc, SLU_Z, SLU_GE); /* Initialize ScalePermstruct and LUstruct. */ +#if defined(SLUD_VERSION_63) + ScalePermstruct = (zScalePermstruct_t *) SUPERLU_MALLOC(sizeof(zScalePermstruct_t)); + LUstruct = (zLUstruct_t *) SUPERLU_MALLOC(sizeof(zLUstruct_t)); + zScalePermstructInit(n,n, ScalePermstruct); +#else ScalePermstruct = (ScalePermstruct_t *) SUPERLU_MALLOC(sizeof(ScalePermstruct_t)); LUstruct = (LUstruct_t *) SUPERLU_MALLOC(sizeof(LUstruct_t)); ScalePermstructInit(n,n, ScalePermstruct); -#if defined(SLUD_VERSION_4) || defined(SLUD_VERSION_5) +#endif +#if defined(SLUD_VERSION_63) + zLUstructInit(n, LUstruct); +#elif defined(SLUD_VERSION_4) || defined(SLUD_VERSION_5) || defined(SLUD_VERSION_6) LUstructInit(n, LUstruct); #elif defined(SLUD_VERSION_3) LUstructInit(n,n, LUstruct); @@ -233,17 +257,23 @@ int mld_zsludist_solve(int itrans, int n, int nrhs, */ #ifdef Have_SLUDist_ SuperMatrix *A; +#if defined(SLUD_VERSION_63) + zScalePermstruct_t *ScalePermstruct; + zLUstruct_t *LUstruct; + zSOLVEstruct_t SOLVEstruct; +#else ScalePermstruct_t *ScalePermstruct; LUstruct_t *LUstruct; SOLVEstruct_t SOLVEstruct; +#endif gridinfo_t *grid; int i, panel_size, permc_spec, relax, info; trans_t trans; double drop_tol = 0.0; double *berr; -#if defined(SLUD_VERSION_5) +#if defined(SLUD_VERSION_63) || defined(SLUD_VERSION_6) ||defined(SLUD_VERSION_5) superlu_dist_options_t options; -#elif defined(SLUD_VERSION_4)||defined(SLUD_VERSION_3) +#elif defined(SLUD_VERSION_4)|| defined(SLUD_VERSION_3) superlu_options_t options; #else choke_on_me; @@ -313,15 +343,21 @@ int mld_zsludist_free(void *f_factors) */ #ifdef Have_SLUDist_ SuperMatrix *A; +#if defined(SLUD_VERSION_63) + zScalePermstruct_t *ScalePermstruct; + zLUstruct_t *LUstruct; + zSOLVEstruct_t SOLVEstruct; +#else ScalePermstruct_t *ScalePermstruct; LUstruct_t *LUstruct; SOLVEstruct_t SOLVEstruct; +#endif gridinfo_t *grid; int i, panel_size, permc_spec, relax; trans_t trans; double drop_tol = 0.0; double *berr; -#if defined(SLUD_VERSION_5) +#if defined(SLUD_VERSION_63)||defined(SLUD_VERSION_6)||defined(SLUD_VERSION_5) superlu_dist_options_t options; #elif defined(SLUD_VERSION_4)||defined(SLUD_VERSION_3) superlu_options_t options; @@ -344,8 +380,13 @@ int mld_zsludist_free(void *f_factors) // we either have a leak or a segfault here. // To be investigated further. //Destroy_CompRowLoc_Matrix_dist(A); +#if defined(SLUD_VERSION_63) + zScalePermstructFree(ScalePermstruct); + zLUstructFree(LUstruct); +#else ScalePermstructFree(ScalePermstruct); LUstructFree(LUstruct); +#endif superlu_gridexit(grid); free(grid); From 2c257321a06a2a6a8b21f3ca87b707b9bc45b056 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 24 Apr 2020 16:18:10 +0200 Subject: [PATCH 11/11] Regenerate configure script from latest updates for SuperLU_DIST --- configure | 151 ++++++++++++++++++++++++++++++++---------------------- 1 file changed, 89 insertions(+), 62 deletions(-) diff --git a/configure b/configure index 47514f7a..151ec7dd 100755 --- a/configure +++ b/configure @@ -1,6 +1,6 @@ #! /bin/sh # Guess values for system-dependent variables and create Makefiles. -# Generated by GNU Autoconf 2.69 for MLD2P4 2.1.1. +# Generated by GNU Autoconf 2.69 for MLD2P4 2.3.1. # # Report bugs to . # @@ -580,8 +580,8 @@ MAKEFLAGS= # Identity of this package. PACKAGE_NAME='MLD2P4' PACKAGE_TARNAME='mld2p4' -PACKAGE_VERSION='2.1.1' -PACKAGE_STRING='MLD2P4 2.1.1' +PACKAGE_VERSION='2.3.1' +PACKAGE_STRING='MLD2P4 2.3.1' PACKAGE_BUGREPORT='https://github.com/sfilippone/mld2p4-2/issues' PACKAGE_URL='' @@ -1337,7 +1337,7 @@ if test "$ac_init_help" = "long"; then # Omit some internal or obsolete options to make the list less imposing. # This message is too long to be a string in the A/UX 3.1 sh. cat <<_ACEOF -\`configure' configures MLD2P4 2.1.1 to adapt to many kinds of systems. +\`configure' configures MLD2P4 2.3.1 to adapt to many kinds of systems. Usage: $0 [OPTION]... [VAR=VALUE]... @@ -1403,7 +1403,7 @@ fi if test -n "$ac_init_help"; then case $ac_init_help in - short | recursive ) echo "Configuration of MLD2P4 2.1.1:";; + short | recursive ) echo "Configuration of MLD2P4 2.3.1:";; esac cat <<\_ACEOF @@ -1572,7 +1572,7 @@ fi test -n "$ac_init_help" && exit $ac_status if $ac_init_version; then cat <<\_ACEOF -MLD2P4 configure 2.1.1 +MLD2P4 configure 2.3.1 generated by GNU Autoconf 2.69 Copyright (C) 2012 Free Software Foundation, Inc. @@ -2208,7 +2208,7 @@ cat >config.log <<_ACEOF This file contains any messages produced by compilers while running configure, to aid debugging if configure makes a mistake. -It was created by MLD2P4 $as_me 2.1.1, which was +It was created by MLD2P4 $as_me 2.3.1, which was generated by GNU Autoconf 2.69. Invocation command line was $ $0 $@ @@ -2559,7 +2559,7 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu # VERSION is the file containing the PSBLAS version code # FIXME -mld2p4_cv_version="2.1.1" +mld2p4_cv_version="2.3.1" # A sample source file @@ -3180,7 +3180,7 @@ fi # Define the identity of the package. PACKAGE='mld2p4' - VERSION='2.1.1' + VERSION='2.3.1' cat >>confdefs.h <<_ACEOF @@ -9132,11 +9132,12 @@ fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext fi - { $as_echo "$as_me:${as_lineno-$LINENO}: result: $pac_sludist_lib_ok" >&5 + { $as_echo "$as_me:${as_lineno-$LINENO}: result: $pac_sludist_lib_ok" >&5 $as_echo "$pac_sludist_lib_ok" >&6; } - if test "x$pac_sludist_lib_ok" == "xyes" ; then - { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 6" >&5 -$as_echo_n "checking for superlu_dist version 6... " >&6; } +fi + +if test "x$pac_sludist_lib_ok" == "xyes" ; then + ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' @@ -9144,41 +9145,60 @@ ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $ ac_compiler_gnu=$ac_cv_c_compiler_gnu ac_cc=${MPICC-$CC} + ac_exeext=""; + CPPFLAGS="$SLUDIST_INCLUDES $save_CPPFLAGS" + LIBS="$SLUDIST_LIBS -lm $save_LIBS"; cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ - #include "superlu_ddefs.h" - int testdslud() - { dLUstruct_t *LUstruct; - int n; - dLUstructInit(n, LUstruct); - } +#include + #include + + void main() + { int i=SUPERLU_DIST_MAJOR_VERSION; + printf("%d\n",i); + } _ACEOF -if ac_fn_c_try_compile "$LINENO"; then : - { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 -$as_echo "yes" >&6; }; pac_sludist_version="6"; +if ac_fn_c_try_link "$LINENO"; then : + mld2p4_cv_superludist_major=`./conftest${ac_exeext} | sed 's/^ *//'` else - { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 -$as_echo "no" >&6; }; pac_sludist_version=""; + mld2p4_cv_superludist_major="unknown" fi -rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext +rm -f core conftest.err conftest.$ac_objext \ + conftest$ac_exeext conftest.$ac_ext + cat confdefs.h - <<_ACEOF >conftest.$ac_ext +/* end confdefs.h. */ +#include + #include + + void main() + { int i=SUPERLU_DIST_MINOR_VERSION; + printf("%d\n",i); + } +_ACEOF +if ac_fn_c_try_link "$LINENO"; then : + mld2p4_cv_superludist_minor=`./conftest${ac_exeext} | sed 's/^ *//'` +else + mld2p4_cv_superludist_minor="unknown" +fi +rm -f core conftest.err conftest.$ac_objext \ + conftest$ac_exeext conftest.$ac_ext ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu - if test "x$pac_sludist_version" == "x" ; then - - { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 4" >&5 + if test "x$mld2p4_cv_superludist_major" == "xunknown" ; then + { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 4" >&5 $as_echo_n "checking for superlu_dist version 4... " >&6; } - ac_ext=c + ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu - ac_cc=${MPICC-$CC} - cat confdefs.h - <<_ACEOF >conftest.$ac_ext + ac_cc=${MPICC-$CC} + cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include "superlu_ddefs.h" int testdslud() @@ -9189,71 +9209,78 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu _ACEOF if ac_fn_c_try_compile "$LINENO"; then : { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 -$as_echo "yes" >&6; }; pac_sludist_version="4"; +$as_echo "yes" >&6; }; mld2p4_cv_superludist_major="4"; mld2p4_cv_superludist_minor=""; else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 -$as_echo "no" >&6; }; pac_sludist_version="3"; +$as_echo "no" >&6; }; mld2p4_cv_superludist_major="3"; mld2p4_cv_superludist_minor=""; fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext - ac_ext=c + ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu - if test "x$pac_sludist_version" == "x4" ; then - { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 5" >&5 + if test "x$mld2p4_cv_superludist_major" == "x4" ; then + { $as_echo "$as_me:${as_lineno-$LINENO}: checking for superlu_dist version 5" >&5 $as_echo_n "checking for superlu_dist version 5... " >&6; } - ac_ext=c + ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu - ac_cc=${MPICC-$CC} - cat confdefs.h - <<_ACEOF >conftest.$ac_ext + ac_cc=${MPICC-$CC} + cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include "superlu_ddefs.h" - int testdslud() - { superlu_dist_options_t options; - int n; - set_default_options_dist(&options); - } + int testdslud() + { superlu_dist_options_t options; + int n; + set_default_options_dist(&options); + } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 -$as_echo "yes" >&6; }; pac_sludist_version="5"; +$as_echo "yes" >&6; }; mld2p4_cv_superludist_major="5"; mld2p4_cv_superludist_minor=""; else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 -$as_echo "no" >&6; }; pac_sludist_version="4"; +$as_echo "no" >&6; }; mld2p4_cv_superludist_major="4"; mld2p4_cv_superludist_minor=""; fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext - ac_ext=c + ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu - + fi fi - fi + { $as_echo "$as_me:${as_lineno-$LINENO}: SuperLU_dist version $mld2p4_cv_superludist_major.$mld2p4_cv_superludist_minor." >&5 +$as_echo "$as_me: SuperLU_dist version $mld2p4_cv_superludist_major.$mld2p4_cv_superludist_minor." >&6;} + else SLUDIST_LIBS=""; SLUDIST_INCLUDES=""; fi -fi - LIBS="$save_LIBS"; CPPFLAGS="$save_CPPFLAGS"; CC="$save_CC"; -ac_ext=c + ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu + if test "x$mld2p4_cv_have_superludist" == "xyes" ; then + pac_sludist_version="$mld2p4_cv_superludist_major"; + if (($mld2p4_cv_superludist_major==6)); then + if (($mld2p4_cv_superludist_minor>=3)); then + pac_sludist_version="63"; + fi + fi SLUDIST_FLAGS="" SLUDIST_FLAGS="-DHave_SLUDist_ -DSLUD_VERSION_$pac_sludist_version $SLUDIST_INCLUDES" FDEFINES="$mld_cv_define_prepend-DHAVE_SLUDIST_ $FDEFINES" @@ -9919,7 +9946,7 @@ cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 # report actual input values of CONFIG_FILES etc. instead of their # values after options handling. ac_log=" -This file was extended by MLD2P4 $as_me 2.1.1, which was +This file was extended by MLD2P4 $as_me 2.3.1, which was generated by GNU Autoconf 2.69. Invocation command line was CONFIG_FILES = $CONFIG_FILES @@ -9976,7 +10003,7 @@ _ACEOF cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 ac_cs_config="`$as_echo "$ac_configure_args" | sed 's/^ //; s/[\\""\`\$]/\\\\&/g'`" ac_cs_version="\\ -MLD2P4 config.status 2.1.1 +MLD2P4 config.status 2.3.1 configured by $0, generated by GNU Autoconf 2.69, with options \\"\$ac_cs_config\\" @@ -10664,10 +10691,10 @@ fi ${PACKAGE_NAME} ${mld2p4_cv_version} has been configured as follows: PSBLAS library : ${PSBLAS_DIR} - MUMPS : ${mld2p4_cv_have_mumps} - SuperLU : ${mld2p4_cv_have_superlu} - SuperLU_Dist : ${mld2p4_cv_have_superludist} - UMFPack : ${mld2p4_cv_have_umfpack} + MUMPS detected : ${mld2p4_cv_have_mumps} + SuperLU detected : ${mld2p4_cv_have_superlu} + SuperLU_Dist detected : ${mld2p4_cv_have_superludist} + UMFPack detected : ${mld2p4_cv_have_umfpack} If you are satisfied, run 'make' to build ${PACKAGE_NAME} and its documentation; otherwise type ./configure --help=short for a complete list of configure options specific to ${PACKAGE_NAME}. @@ -10676,10 +10703,10 @@ $as_echo "$as_me: ${PACKAGE_NAME} ${mld2p4_cv_version} has been configured as follows: PSBLAS library : ${PSBLAS_DIR} - MUMPS : ${mld2p4_cv_have_mumps} - SuperLU : ${mld2p4_cv_have_superlu} - SuperLU_Dist : ${mld2p4_cv_have_superludist} - UMFPack : ${mld2p4_cv_have_umfpack} + MUMPS detected : ${mld2p4_cv_have_mumps} + SuperLU detected : ${mld2p4_cv_have_superlu} + SuperLU_Dist detected : ${mld2p4_cv_have_superludist} + UMFPack detected : ${mld2p4_cv_have_umfpack} If you are satisfied, run 'make' to build ${PACKAGE_NAME} and its documentation; otherwise type ./configure --help=short for a complete list of configure options specific to ${PACKAGE_NAME}.