From 153a3714d830ed73e2f5716eadcac14ba382875c Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Wed, 21 Feb 2007 13:09:43 +0000 Subject: [PATCH] Taken out jac_sweeps and iren. Modified USE statements. --- prec/Makefile | 2 - prec/psb_dbjac_aply.f90 | 98 +++------- prec/psb_ddiagsc_bld.f90 | 2 +- prec/psb_dgprec_aply.f90 | 18 +- prec/psb_dilu_bld.f90 | 135 +++----------- prec/psb_dprc_aply.f90 | 36 +--- prec/psb_dprecbld.f90 | 28 +-- prec/psb_dprecset.f90 | 8 +- prec/psb_dsp_renum.f90 | 390 --------------------------------------- prec/psb_prec_mod.f90 | 113 ++++++++++++ prec/psb_prec_type.f90 | 29 ++- prec/psb_zbjac_aply.f90 | 109 +++-------- prec/psb_zdiagsc_bld.f90 | 2 +- prec/psb_zgprec_aply.f90 | 19 +- prec/psb_zilu_bld.f90 | 130 +++---------- prec/psb_zprc_aply.f90 | 37 +--- prec/psb_zprecbld.f90 | 29 +-- prec/psb_zprecset.f90 | 8 +- prec/psb_zsp_renum.f90 | 388 -------------------------------------- 19 files changed, 244 insertions(+), 1337 deletions(-) delete mode 100644 prec/psb_dsp_renum.f90 delete mode 100644 prec/psb_zsp_renum.f90 diff --git a/prec/Makefile b/prec/Makefile index 88a4da3f..6530ea59 100644 --- a/prec/Makefile +++ b/prec/Makefile @@ -4,13 +4,11 @@ LIBDIR=../lib HERE=. MODOBJS= psb_prec_type.o psb_prec_mod.o F90OBJS= psb_dilu_bld.o psb_dilu_fct.o\ - psb_dsp_renum.o\ psb_dprecbld.o psb_dprecset.o \ psb_ddiagsc_bld.o \ psb_dprc_aply.o \ psb_dgprec_aply.o psb_dbjac_aply.o\ psb_zilu_bld.o psb_zilu_fct.o\ - psb_zsp_renum.o\ psb_zprecbld.o psb_zprecset.o \ psb_zdiagsc_bld.o \ psb_zprc_aply.o psb_zgprec_aply.o psb_zbjac_aply.o diff --git a/prec/psb_dbjac_aply.f90 b/prec/psb_dbjac_aply.f90 index 8addae4c..845c7572 100644 --- a/prec/psb_dbjac_aply.f90 +++ b/prec/psb_dbjac_aply.f90 @@ -37,7 +37,7 @@ subroutine psb_dbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) ! use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_dbjac_aply implicit none type(psb_desc_type), intent(in) :: desc_data @@ -98,91 +98,41 @@ subroutine psb_dbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) goto 9999 end if endif - - if (prec%iprcparm(jac_sweeps_) == 1) then - select case(prec%iprcparm(f_type_)) - case(f_ilu_n_,f_ilu_e_) - select case(trans) - case('N','n') + select case(prec%iprcparm(f_type_)) + case(f_ilu_n_,f_ilu_e_) - call psb_spsm(done,prec%av(l_pr_),x,dzero,ww,desc_data,info,& - & trans='N',unit=diagl,choice=psb_none_,work=aux) - if(info /=0) goto 9999 - ww(1:n_row) = ww(1:n_row)*prec%d(1:n_row) - call psb_spsm(alpha,prec%av(u_pr_),ww,beta,y,desc_data,info,& - & trans='N',unit=diagu,choice=psb_none_, work=aux) - if(info /=0) goto 9999 + select case(trans) + case('N','n') - case('T','t','C','c') - call psb_spsm(done,prec%av(u_pr_),x,dzero,ww,desc_data,info,& - & trans=trans,unit=diagu,choice=psb_none_, work=aux) - if(info /=0) goto 9999 - ww(1:n_row) = ww(1:n_row)*prec%d(1:n_row) - call psb_spsm(alpha,prec%av(l_pr_),ww,beta,y,desc_data,info,& - & trans=trans,unit=diagl,choice=psb_none_,work=aux) - if(info /=0) goto 9999 + call psb_spsm(done,prec%av(l_pr_),x,dzero,ww,desc_data,info,& + & trans='N',unit=diagl,choice=psb_none_,work=aux) + if(info /=0) goto 9999 + ww(1:n_row) = ww(1:n_row)*prec%d(1:n_row) + call psb_spsm(alpha,prec%av(u_pr_),ww,beta,y,desc_data,info,& + & trans='N',unit=diagu,choice=psb_none_, work=aux) + if(info /=0) goto 9999 - end select - - - case default - write(0,*) 'Unknown factorization type in bjac_aply',prec%iprcparm(f_type_) - end select - if (debugprt) write(0,*)' Y: ',y(:) - - else if (prec%iprcparm(jac_sweeps_) > 1) then - - ! Note: we have to add TRANS to this one !!!!!!!!! - - if (size(prec%av) < ap_nd_) then - info = 4011 - goto 9999 - endif - - allocate(tx(n_col),ty(n_col),stat=info) - if (info /= 0) then - call psb_errpush(4010,name,a_err='Allocate') - goto 9999 - end if - - tx = dzero - ty = dzero - select case(prec%iprcparm(f_type_)) - case(f_ilu_n_,f_ilu_e_) - do i=1, prec%iprcparm(jac_sweeps_) - ! X(k+1) = M^-1*(b-N*X(k)) - ty(1:n_row) = x(1:n_row) - call psb_spmm(-done,prec%av(ap_nd_),tx,done,ty,& - & prec%desc_data,info,work=aux) - if(info /=0) goto 9999 - call psb_spsm(done,prec%av(l_pr_),ty,dzero,ww,& - & prec%desc_data,info,& - & trans='N',unit='U',choice=psb_none_,work=aux) - if(info /=0) goto 9999 - ww(1:n_row) = ww(1:n_row)*prec%d(1:n_row) - call psb_spsm(done,prec%av(u_pr_),ww,dzero,tx,& - & prec%desc_data,info,& - & trans='N',unit='U',choice=psb_none_,work=aux) - if(info /=0) goto 9999 - end do + case('T','t','C','c') + call psb_spsm(done,prec%av(u_pr_),x,dzero,ww,desc_data,info,& + & trans=trans,unit=diagu,choice=psb_none_, work=aux) + if(info /=0) goto 9999 + ww(1:n_row) = ww(1:n_row)*prec%d(1:n_row) + call psb_spsm(alpha,prec%av(l_pr_),ww,beta,y,desc_data,info,& + & trans=trans,unit=diagl,choice=psb_none_,work=aux) + if(info /=0) goto 9999 end select - - call psb_geaxpby(alpha,tx,beta,y,desc_data,info) - - - deallocate(tx,ty) - - else - goto 9999 + case default + write(0,*) 'Unknown factorization type in bjac_aply',prec%iprcparm(f_type_) + end select + if (debugprt) write(0,*)' Y: ',y(:) - endif if (n_col <= size(work)) then if ((4*n_col+n_col) <= size(work)) then diff --git a/prec/psb_ddiagsc_bld.f90 b/prec/psb_ddiagsc_bld.f90 index 1fc771ef..2db6a385 100644 --- a/prec/psb_ddiagsc_bld.f90 +++ b/prec/psb_ddiagsc_bld.f90 @@ -31,7 +31,7 @@ subroutine psb_ddiagsc_bld(a,desc_a,p,upd,info) use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_ddiagsc_bld Implicit None type(psb_dspmat_type), target :: a diff --git a/prec/psb_dgprec_aply.f90 b/prec/psb_dgprec_aply.f90 index c9c60116..d1f7b992 100644 --- a/prec/psb_dgprec_aply.f90 +++ b/prec/psb_dgprec_aply.f90 @@ -35,7 +35,7 @@ subroutine psb_dgprec_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) ! use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_dgprec_aply implicit none type(psb_desc_type),intent(in) :: desc_data @@ -55,21 +55,7 @@ subroutine psb_dgprec_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) logical,parameter :: debug=.false., debugprt=.false. character(len=20) :: name, ch_err - interface psb_bjac_aply - subroutine psb_dbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) - use psb_base_mod - use psb_prec_type - type(psb_desc_type), intent(in) :: desc_data - type(psb_dprec_type), intent(in) :: prec - real(kind(0.d0)),intent(inout) :: x(:), y(:) - real(kind(0.d0)),intent(in) :: alpha,beta - character(len=1) :: trans - real(kind(0.d0)),target :: work(:) - integer, intent(out) :: info - end subroutine psb_dbjac_aply - end interface - - name='psb_baseprc_aply' + name='psb_dgprec_aply' info = 0 call psb_erractionsave(err_act) diff --git a/prec/psb_dilu_bld.f90 b/prec/psb_dilu_bld.f90 index b60a0fd4..e10becef 100644 --- a/prec/psb_dilu_bld.f90 +++ b/prec/psb_dilu_bld.f90 @@ -30,7 +30,7 @@ !!$ subroutine psb_dilu_bld(a,desc_a,p,upd,info) use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_dilu_bld implicit none ! ! .. Scalar Arguments .. @@ -53,35 +53,10 @@ subroutine psb_dilu_bld(a,desc_a,p,upd,info) integer :: ictxt,np,me character(len=20) :: name, ch_err - interface psb_ilu_fct - subroutine psb_dilu_fct(a,l,u,d,info,blck) - use psb_base_mod - integer, intent(out) :: info - type(psb_dspmat_type),intent(in) :: a - type(psb_dspmat_type),intent(inout) :: l,u - type(psb_dspmat_type),intent(in), optional, target :: blck - real(kind(1.d0)), intent(inout) :: d(:) - end subroutine psb_dilu_fct - end interface - - interface psb_sp_renum - subroutine psb_dsp_renum(a,desc_a,p,atmp,info) - use psb_base_mod - use psb_prec_type - implicit none - - ! .. array Arguments .. - type(psb_dspmat_type), intent(in) :: a - type(psb_dspmat_type), intent(inout) :: atmp - type(psb_dprec_type), intent(inout) :: p - type(psb_desc_type), intent(in) :: desc_a - integer, intent(out) :: info - end subroutine psb_dsp_renum - end interface if(psb_get_errstatus().ne.0) return info=0 - name='psb_ilu_bld' + name='psb_dilu_bld' call psb_erractionsave(err_act) ictxt=psb_cd_get_context(desc_a) @@ -144,91 +119,30 @@ subroutine psb_dilu_bld(a,desc_a,p,upd,info) end if endif + t3 = psb_wtime() + ! This is where we have mo renumbering, thus no need + ! for ATMP - if (p%iprcparm(iren_) > 0) then - - ! - ! Here we allocate a full copy to hold local A and received BLK - ! - - nztota = psb_sp_get_nnzeros(a) - call psb_sp_all(atmp,nztota,info) - if(info/=0) then - info=4011 - call psb_errpush(info,name) - goto 9999 - end if - - - ! write(0,*) 'ILU_BLD ',nztota,nztotb,a%m - - call psb_sp_renum(a,desc_a,p,atmp,info) - - if(info/=0) then - info=4010 - ch_err='psb_sp_renum' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - - t3 = psb_wtime() - if (debugprt) then - call psb_barrier(ictxt) - open(40+me) - call psb_csprt(40+me,atmp,head='% Local matrix') - close(40+me) - endif - if (debug) write(0,*) me,' Factoring rows ',& - &atmp%m,a%m,atmp%ia2(atmp%m+1)-1 - - ! - ! Ok, factor the matrix. - ! - t5 = psb_wtime() - blck%m=0 - call psb_ilu_fct(atmp,p%av(l_pr_),p%av(u_pr_),p%d,info) - if(info/=0) then - info=4010 - ch_err='psb_ilu_fct' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - - call psb_sp_free(atmp,info) - if(info/=0) then - info=4010 - ch_err='psb_sp_free' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - - - else if (p%iprcparm(iren_) == 0) then - t3 = psb_wtime() - ! This is where we have mo renumbering, thus no need - ! for ATMP - - if (debugprt) then - open(40+me) - call psb_barrier(ictxt) - call psb_csprt(40+me,a,iv=p%desc_data%loc_to_glob,& - & head='% Local matrix') - close(40+me) - endif - - t5= psb_wtime() - if (debug) write(0,*) me,' Going for ilu_fct' - if (debug) call psb_barrier(ictxt) - call psb_ilu_fct(a,p%av(l_pr_),p%av(u_pr_),p%d,info) - if(info/=0) then - info=4010 - ch_err='psb_ilu_fct' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - if (debug) write(0,*) me,' Done dilu_fct' + if (debugprt) then + open(40+me) + call psb_barrier(ictxt) + call psb_csprt(40+me,a,iv=p%desc_data%loc_to_glob,& + & head='% Local matrix') + close(40+me) endif + t5= psb_wtime() + if (debug) write(0,*) me,' Going for ilu_fct' + if (debug) call psb_barrier(ictxt) + call psb_ilu_fct(a,p%av(l_pr_),p%av(u_pr_),p%d,info) + if(info/=0) then + info=4010 + ch_err='psb_ilu_fct' + call psb_errpush(info,name,a_err=ch_err) + goto 9999 + end if + if (debug) write(0,*) me,' Done dilu_fct' + if (debugprt) then ! @@ -244,8 +158,7 @@ subroutine psb_dilu_bld(a,desc_a,p,upd,info) call psb_csprt(80+me,p%av(u_pr_),head='% Local U factor') close(80+me) - endif - + end if ! ierr = MPE_Log_event( ifcte, 0, "st SIMPLE" ) t6 = psb_wtime() diff --git a/prec/psb_dprc_aply.f90 b/prec/psb_dprc_aply.f90 index 3ad5b002..c375c8e5 100644 --- a/prec/psb_dprc_aply.f90 +++ b/prec/psb_dprc_aply.f90 @@ -31,7 +31,7 @@ subroutine psb_dprc_aply(prec,x,y,desc_data,info,trans, work) use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_dprc_aply implicit none type(psb_desc_type),intent(in) :: desc_data @@ -48,20 +48,6 @@ subroutine psb_dprc_aply(prec,x,y,desc_data,info,trans, work) logical,parameter :: debug=.false., debugprt=.false. character(len=20) :: name - interface psb_gprec_aply - subroutine psb_dgprec_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) - use psb_base_mod - use psb_prec_type - type(psb_desc_type),intent(in) :: desc_data - type(psb_dprec_type), intent(in) :: prec - real(kind(0.d0)),intent(inout) :: x(:), y(:) - real(kind(0.d0)),intent(in) :: alpha,beta - character(len=1) :: trans - real(kind(0.d0)),target :: work(:) - integer, intent(out) :: info - end subroutine psb_dgprec_aply - end interface - name='psb_prc_aply' info = 0 call psb_erractionsave(err_act) @@ -146,7 +132,7 @@ end subroutine psb_dprc_aply subroutine psb_dprc_aply1(prec,x,desc_data,info,trans) use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_dprc_aply1 implicit none type(psb_desc_type),intent(in) :: desc_data @@ -156,28 +142,12 @@ subroutine psb_dprc_aply1(prec,x,desc_data,info,trans) character(len=1), optional :: trans logical,parameter :: debug=.false., debugprt=.false. - interface - subroutine psb_dprc_aply(prec,x,y,desc_data,info,trans, work) - - use psb_base_mod - use psb_prec_type - implicit none - - type(psb_desc_type),intent(in) :: desc_data - type(psb_dprec_type), intent(in) :: prec - real(kind(0.d0)),intent(inout) :: x(:), y(:) - integer, intent(out) :: info - character(len=1), optional :: trans - real(kind(0.d0)), optional, target :: work(:) - end subroutine psb_dprc_aply - end interface - ! Local variables character :: trans_ integer :: ictxt,np,me,i, err_act real(kind(1.d0)), pointer :: WW(:), w1(:) character(len=20) :: name - name='psb_dprec1' + name='psb_dprec_aply1' info = 0 call psb_erractionsave(err_act) diff --git a/prec/psb_dprecbld.f90 b/prec/psb_dprecbld.f90 index 5e62458d..6f841886 100644 --- a/prec/psb_dprecbld.f90 +++ b/prec/psb_dprecbld.f90 @@ -31,7 +31,7 @@ subroutine psb_dprecbld(a,desc_a,p,info,upd) use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_dprecbld Implicit None type(psb_dspmat_type), target :: a @@ -40,30 +40,6 @@ subroutine psb_dprecbld(a,desc_a,p,info,upd) integer, intent(out) :: info character, intent(in), optional :: upd - interface psb_diagsc_bld - subroutine psb_ddiagsc_bld(a,desc_data,p,upd,info) - use psb_base_mod - use psb_prec_type - integer, intent(out) :: info - type(psb_dspmat_type), intent(in), target :: a - type(psb_desc_type),intent(in) :: desc_data - type(psb_dprec_type), intent(inout) :: p - character, intent(in) :: upd - end subroutine psb_ddiagsc_bld - end interface - - interface psb_ilu_bld - subroutine psb_dilu_bld(a,desc_data,p,upd,info) - use psb_base_mod - use psb_prec_type - integer, intent(out) :: info - type(psb_dspmat_type), intent(in), target :: a - type(psb_desc_type),intent(in) :: desc_data - type(psb_dprec_type), intent(inout) :: p - character, intent(in) :: upd - end subroutine psb_dilu_bld - end interface - ! Local scalars Integer :: err, nnzero, n_row, n_col,I,j,k,ictxt,& & me,mycol,np,npcol,mglob,lw, mtype, nrg, nzg, err_act @@ -138,8 +114,6 @@ subroutine psb_dprecbld(a,desc_a,p,info,upd) case (bjac_) - call psb_check_def(p%iprcparm(iren_),'renumbering',& - & renum_none_,is_legal_renum) call psb_check_def(p%iprcparm(f_type_),'fact',& & f_ilu_n_,is_legal_ml_fact) diff --git a/prec/psb_dprecset.f90 b/prec/psb_dprecset.f90 index 117bd9e5..98f7ce2d 100644 --- a/prec/psb_dprecset.f90 +++ b/prec/psb_dprecset.f90 @@ -31,7 +31,7 @@ subroutine psb_dprecset(p,ptype,info,iv,rs,rv) use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_dprecset implicit none type(psb_dprec_type), intent(inout) :: p character(len=*), intent(in) :: ptype @@ -56,23 +56,17 @@ subroutine psb_dprecset(p,ptype,info,iv,rs,rv) p%iprcparm(:) = 0 p%iprcparm(p_type_) = noprec_ p%iprcparm(f_type_) = f_none_ - p%iprcparm(iren_) = 0 - p%iprcparm(jac_sweeps_) = 1 case ('DIAG') p%iprcparm(:) = 0 p%iprcparm(p_type_) = diag_ p%iprcparm(f_type_) = f_none_ - p%iprcparm(iren_) = 0 - p%iprcparm(jac_sweeps_) = 1 case ('BJAC') p%iprcparm(:) = 0 p%iprcparm(p_type_) = bjac_ p%iprcparm(f_type_) = f_ilu_n_ - p%iprcparm(iren_) = 0 p%iprcparm(ilu_fill_in_) = 0 - p%iprcparm(jac_sweeps_) = 1 case default write(0,*) 'Unknown preconditioner type request "',ptype,'"' diff --git a/prec/psb_dsp_renum.f90 b/prec/psb_dsp_renum.f90 deleted file mode 100644 index c51bee39..00000000 --- a/prec/psb_dsp_renum.f90 +++ /dev/null @@ -1,390 +0,0 @@ -!!$ -!!$ Parallel Sparse BLAS v2.0 -!!$ (C) Copyright 2006 Salvatore Filippone University of Rome Tor Vergata -!!$ Alfredo Buttari University of Rome Tor Vergata -!!$ -!!$ Redistribution and use in source and binary forms, with or without -!!$ modification, are permitted provided that the following conditions -!!$ are met: -!!$ 1. Redistributions of source code must retain the above copyright -!!$ notice, this list of conditions and the following disclaimer. -!!$ 2. Redistributions in binary form must reproduce the above copyright -!!$ notice, this list of conditions, and the following disclaimer in the -!!$ documentation and/or other materials provided with the distribution. -!!$ 3. The name of the PSBLAS group or the names of its contributors may -!!$ not be used to endorse or promote products derived from this -!!$ software without specific written permission. -!!$ -!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -!!$ PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS -!!$ BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -!!$ CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -!!$ SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -!!$ INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -!!$ POSSIBILITY OF SUCH DAMAGE. -!!$ -!!$ -subroutine psb_dsp_renum(a,desc_a,p,atmp,info) - use psb_base_mod - use psb_prec_type - implicit none - - ! .. array Arguments .. - type(psb_dspmat_type), intent(in) :: a - type(psb_dspmat_type), intent(inout) :: atmp - type(psb_dprec_type), intent(inout) :: p - type(psb_desc_type), intent(in) :: desc_a - integer, intent(out) :: info - - - character(len=20) :: name, ch_err - integer nztota, nztotb, nztmp, nzl, nnr, ir, mglob, mtype, n_row, & - & nrow_a,n_col, nhalo,lovr, ind, iind, pi,nr,ns,i,j,jj,k,kk - integer ::ictxt,np,me, err_act - integer, allocatable :: itmp(:), itmp2(:) - real(kind(1.d0)), allocatable :: rtmp(:) - real(kind(1.d0)) :: t1,t2,t3,t4,t5,t6, t7, t8 - - if (psb_get_errstatus().ne.0) return - info=0 - name='apply_renum' - call psb_erractionsave(err_act) - - ictxt=psb_cd_get_context(desc_a) - - call psb_info(ictxt, me, np) - -!!!!!!!!!!!!!!!! CHANGE FOR NON-CSR A - ! - ! Renumbering type: - ! 1. Global column indices - ! (2. GPS band reduction disabled for the time being) - - if (p%iprcparm(iren_)==renum_glb_) then - atmp%m = a%m - atmp%k = a%k - atmp%fida='CSR' - atmp%descra = 'GUN' - - ! This is the renumbering coherent with global indices.. - mglob = psb_cd_get_global_rows(desc_a) - - ! - ! Remember: we have switched IA1=COLS and IA2=ROWS - ! Now identify the set of distinct local column indices - ! - - nnr = p%desc_data%matrix_data(psb_n_row_) - allocate(p%perm(nnr),p%invperm(nnr),itmp2(nnr),stat=info) - if (info /= 0) then - call psb_errpush(4010,name,a_err='Allocate') - goto 9999 - end if - - do k=1,nnr - itmp2(k) = p%desc_data%loc_to_glob(k) - enddo - ! - ! We want: NEW(I) = OLD(PERM(I)) - ! - call psb_msort(itmp2(1:nnr),ix=p%perm) - - do k=1, nnr - p%invperm(p%perm(k)) = k - enddo - t3 = psb_wtime() - - ! Build ATMP with new numbering. - nztmp=size(atmp%aspk) - allocate(itmp(max(8,atmp%m+2,nztmp+2)),rtmp(atmp%m),stat=info) - if (info /= 0) then - call psb_errpush(4010,name,a_err='Allocate') - goto 9999 - end if - - j = 1 - atmp%ia2(1) = 1 - do i=1, atmp%m - ir = p%perm(i) - - if (ir <= a%m ) then - - nzl = a%ia2(ir+1) - a%ia2(ir) - if (nzl > size(rtmp)) then - call psb_realloc(nzl,rtmp,info) - if(info/=0) then - info=4010 - ch_err='psb_realloc' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - endif - jj = a%ia2(ir) - k=0 - do kk=1, nzl - if (a%ia1(jj+kk-1)<=atmp%m) then - k = k + 1 - rtmp(k) = a%aspk(jj+kk-1) - atmp%ia1(j+k-1) = p%invperm(a%ia1(jj+kk-1)) - endif - enddo - call psb_msort(atmp%ia1(j:j+k-1),ix=itmp2) - do kk=1,k - atmp%aspk(j+kk-1) = rtmp(itmp2(kk)) - enddo - - - else - write(0,*) 'Row index error 1 :',i,ir - endif - - j = j + k - atmp%ia2(i+1) = j - - enddo - - t4 = psb_wtime() - - - deallocate(itmp,itmp2,rtmp) - - else if (p%iprcparm(iren_)==renum_gps_) then - - atmp%m = a%m - atmp%k = a%k - atmp%fida='CSR' - atmp%descra = 'GUN' - do i=1, a%m - atmp%ia2(i) = a%ia2(i) - do j= a%ia2(i), a%ia2(i+1)-1 - atmp%ia1(j) = a%ia1(j) - enddo - enddo - atmp%ia2(a%m+1) = a%ia2(a%m+1) - nztmp = atmp%ia2(atmp%m+1) - 1 - - - ! This is a renumbering with Gibbs-Poole-Stockmeyer - ! band reduction. Switched off for now. To be fixed, - ! gps_reduction should get p%perm. - - ! write(0,*) me,' Renumbering: realloc perms',atmp%m - call psb_realloc(atmp%m,p%perm,info) - if(info/=0) then - info=4010 - ch_err='psb_realloc' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - - call psb_realloc(atmp%m,p%invperm,info) - if(info/=0) then - info=4010 - ch_err='psb_realloc' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - - allocate(itmp(max(8,atmp%m+2,nztmp+2)),stat=info) - if (info /= 0) then - call psb_errpush(4010,name,a_err='Allocate') - goto 9999 - end if - - itmp(1:8) = 0 - ! write(0,*) me,' Renumbering: Calling Metis' - - ! write(0,*) size(p%av(u_pr_)%pl),size(p%av(l_pr_)%pr) - call gps_reduction(atmp%m,atmp%ia2,atmp%ia1,p%perm,p%invperm,info) - if(info/=0) then - info=4010 - ch_err='gps_reduction' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - - ! write(0,*) me,' Renumbering: Done GPS' - ! call psb_barrier(ictxt) - do i=1, atmp%m - if (p%perm(i) /= i) then - write(0,*) me,' permutation is not identity ' - exit - endif - enddo - - - do k=1, nnr - p%invperm(p%perm(k)) = k - enddo - t3 = psb_wtime() - - ! Build ATMP with new numbering. - - allocate(itmp2(max(8,atmp%m+2,nztmp+2)),rtmp(atmp%m),stat=info) - if (info /= 0) then - call psb_errpush(4010,name,a_err='Allocate') - goto 9999 - end if - - j = 1 - atmp%ia2(1) = 1 - do i=1, atmp%m - ir = p%perm(i) - - if (ir <= a%m ) then - - nzl = a%ia2(ir+1) - a%ia2(ir) - if (nzl > size(rtmp)) then - call psb_realloc(nzl,rtmp,info) - if(info/=0) then - info=4010 - ch_err='psb_realloc' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - endif - jj = a%ia2(ir) - k=0 - do kk=1, nzl - if (a%ia1(jj+kk-1)<=atmp%m) then - k = k + 1 - rtmp(k) = a%aspk(jj+kk-1) - atmp%ia1(j+k-1) = p%invperm(a%ia1(jj+kk-1)) - endif - enddo - call psb_msort(atmp%ia1(j:j+k-1),ix=itmp2) - do kk=1,k - atmp%aspk(j+kk-1) = rtmp(itmp2(kk)) - enddo - - else - write(0,*) 'Row index error 1 :',i,ir - endif - - j = j + k - atmp%ia2(i+1) = j - - enddo - - t4 = psb_wtime() - - - - deallocate(itmp,itmp2,rtmp) - - end if - - call psb_erractionrestore(err_act) - return - -9999 continue - call psb_erractionrestore(err_act) - if (err_act.eq.psb_act_abort_) then - call psb_error() - return - end if - return - -contains - - - subroutine gps_reduction(m,ia,ja,perm,iperm,info) - integer i,j,dgConn,Npnt,m - integer n,idpth,ideg,ibw2,ipf2 - integer,dimension(:) :: perm,iperm,ia,ja - integer, intent(out) :: info - - integer,dimension(:,:),allocatable::NDstk - integer,dimension(:),allocatable::iOld,renum,ndeg,lvl,lvls1,lvls2,ccstor - !--- Per la common area. - - character(len=20) :: name, ch_err - - if(psb_get_errstatus().ne.0) return - info=0 - name='gps_reduction' - call psb_erractionsave(err_act) - - - !--- Calcolo il massimo grado di connettivita'. - npnt = m - write(6,*) ' GPS su ',npnt - dgConn=0 - do i=1,m - dgconn = max(dgconn,(ia(i+1)-ia(i))) - enddo - !--- Il max valore di connettivita' e "dgConn" - - !--- Valori della common - n=Npnt !--- Numero di righe - iDeg=dgConn !--- Massima connettivita' - ! iDpth= !--- Numero di livelli non serve settarlo - - allocate(NDstk(Npnt,dgConn),stat=info) - if (info/=0) then - info=4000 - call psb_errpush(info,name) - goto 9999 - else - write(0,*) 'gps_reduction first alloc OK' - endif - allocate(iOld(Npnt),renum(Npnt+1),ndeg(Npnt),lvl(Npnt),lvls1(Npnt),& - &lvls2(Npnt),ccstor(Npnt),stat=info) - if (info/=0) then - info=4000 - call psb_errpush(info,name) - goto 9999 - else - write(0,*) 'gps_reduction 2nd alloc OK' - endif - - !--- Prepariamo il grafo della matrice - Ndstk(:,:)=0 - do i=1,Npnt - k=0 - do j = ia(i),ia(i+1) - 1 - if ((1<=ja(j)).and.( ja( j ) /= i ).and.(ja(j)<=npnt)) then - k = k+1 - Ndstk(i,k)=ja(j) - endif - enddo - ndeg(i)=k - enddo - - !--- Numerazione. - do i=1,Npnt - iOld(i)=i - enddo - write(0,*) 'gps_red : Preparation done' - !--- - !--- Chiamiamo funzione reduce. - call psb_gps_reduce(Ndstk,Npnt,iOld,renum,ndeg,lvl,lvls1, lvls2,ccstor,& - & ibw2,ipf2,n,idpth,ideg) - write(0,*) 'gps_red : Done reduce' - !--- Permutazione - perm(1:Npnt)=renum(1:Npnt) - !--- Inversa permutazione - do i=1,Npnt - iperm(perm(i))=i - enddo - !--- Puliamo tutto. - deallocate(NDstk,iOld,renum,ndeg,lvl,lvls1,lvls2,ccstor) - - call psb_erractionrestore(err_act) - return - -9999 continue - call psb_erractionrestore(err_act) - if (err_act.eq.psb_act_abort_) then - call psb_error() - return - end if - return - - end subroutine gps_reduction - -end subroutine psb_dsp_renum diff --git a/prec/psb_prec_mod.f90 b/prec/psb_prec_mod.f90 index b8a4c48f..1aa7e108 100644 --- a/prec/psb_prec_mod.f90 +++ b/prec/psb_prec_mod.f90 @@ -122,4 +122,117 @@ module psb_prec_mod end subroutine psb_zprc_aply1 end interface + + interface psb_bjac_aply + subroutine psb_dbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) + use psb_base_mod + use psb_prec_type + type(psb_desc_type), intent(in) :: desc_data + type(psb_dprec_type), intent(in) :: prec + real(kind(0.d0)),intent(inout) :: x(:), y(:) + real(kind(0.d0)),intent(in) :: alpha,beta + character(len=1) :: trans + real(kind(0.d0)),target :: work(:) + integer, intent(out) :: info + end subroutine psb_dbjac_aply + subroutine psb_zbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) + use psb_base_mod + use psb_prec_type + type(psb_desc_type), intent(in) :: desc_data + type(psb_zprec_type), intent(in) :: prec + complex(kind(0.d0)),intent(inout) :: x(:), y(:) + complex(kind(0.d0)),intent(in) :: alpha,beta + character(len=1) :: trans + complex(kind(0.d0)),target :: work(:) + integer, intent(out) :: info + end subroutine psb_zbjac_aply + end interface + + interface psb_ilu_fct + subroutine psb_dilu_fct(a,l,u,d,info,blck) + use psb_base_mod + integer, intent(out) :: info + type(psb_dspmat_type),intent(in) :: a + type(psb_dspmat_type),intent(inout) :: l,u + type(psb_dspmat_type),intent(in), optional, target :: blck + real(kind(1.d0)), intent(inout) :: d(:) + end subroutine psb_dilu_fct + subroutine psb_zilu_fct(a,l,u,d,info,blck) + use psb_base_mod + integer, intent(out) :: info + type(psb_zspmat_type),intent(in) :: a + type(psb_zspmat_type),intent(inout) :: l,u + type(psb_zspmat_type),intent(in), optional, target :: blck + complex(kind(1.d0)), intent(inout) :: d(:) + end subroutine psb_zilu_fct + end interface + + interface psb_ilu_bld + subroutine psb_dilu_bld(a,desc_a,p,upd,info) + use psb_base_mod + use psb_prec_type + integer, intent(out) :: info + type(psb_dspmat_type), intent(in), target :: a + type(psb_dprec_type), intent(inout) :: p + type(psb_desc_type), intent(in) :: desc_a + character, intent(in) :: upd + end subroutine psb_dilu_bld + subroutine psb_zilu_bld(a,desc_a,p,upd,info) + use psb_base_mod + use psb_prec_type + integer, intent(out) :: info + type(psb_zspmat_type), intent(in), target :: a + type(psb_zprec_type), intent(inout) :: p + type(psb_desc_type), intent(in) :: desc_a + character, intent(in) :: upd + end subroutine psb_zilu_bld + end interface + + interface psb_diagsc_bld + subroutine psb_ddiagsc_bld(a,desc_a,p,upd,info) + use psb_base_mod + use psb_prec_type + integer, intent(out) :: info + type(psb_dspmat_type), intent(in), target :: a + type(psb_dprec_type), intent(inout) :: p + type(psb_desc_type), intent(in) :: desc_a + character, intent(in) :: upd + end subroutine psb_ddiagsc_bld + subroutine psb_zdiagsc_bld(a,desc_a,p,upd,info) + use psb_base_mod + use psb_prec_type + integer, intent(out) :: info + type(psb_zspmat_type), intent(in), target :: a + type(psb_zprec_type), intent(inout) :: p + type(psb_desc_type), intent(in) :: desc_a + character, intent(in) :: upd + end subroutine psb_zdiagsc_bld + end interface + + interface psb_gprec_aply + subroutine psb_dgprec_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) + use psb_base_mod + use psb_prec_type + type(psb_desc_type),intent(in) :: desc_data + type(psb_dprec_type), intent(in) :: prec + real(kind(0.d0)),intent(inout) :: x(:), y(:) + real(kind(0.d0)),intent(in) :: alpha,beta + character(len=1) :: trans + real(kind(0.d0)),target :: work(:) + integer, intent(out) :: info + end subroutine psb_dgprec_aply + + subroutine psb_zgprec_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) + use psb_base_mod + use psb_prec_type + type(psb_desc_type),intent(in) :: desc_data + type(psb_zprec_type), intent(in) :: prec + complex(kind(0.d0)),intent(inout) :: x(:), y(:) + complex(kind(0.d0)),intent(in) :: alpha,beta + character(len=1) :: trans + complex(kind(0.d0)),target :: work(:) + integer, intent(out) :: info + end subroutine psb_zgprec_aply + end interface + end module psb_prec_mod diff --git a/prec/psb_prec_type.f90 b/prec/psb_prec_type.f90 index 7c172ab9..8e3348e9 100644 --- a/prec/psb_prec_type.f90 +++ b/prec/psb_prec_type.f90 @@ -45,8 +45,8 @@ module psb_prec_type ! prolongation type, restriction type, renumbering algorithm, ! number of overlap layers, pointer to SuperLU factors, ! levels of fill in for ILU(N), - integer, parameter :: p_type_=1, f_type_=2, iren_=5 - integer, parameter :: ilu_fill_in_=8, jac_sweeps_=9 + integer, parameter :: p_type_=1, f_type_=2 + integer, parameter :: ilu_fill_in_=8 !Renumbering. SEE BELOW integer, parameter :: renum_none_=0, renum_glb_=1, renum_gps_=2 integer, parameter :: ifpsz=10 @@ -106,16 +106,19 @@ module psb_prec_type contains subroutine psb_out_prec_descr(p) + use psb_base_mod type(psb_dprec_type), intent(in) :: p call psb_file_prec_descr(6,p) end subroutine psb_out_prec_descr subroutine psb_zout_prec_descr(p) + use psb_base_mod type(psb_zprec_type), intent(in) :: p call psb_zfile_prec_descr(6,p) end subroutine psb_zout_prec_descr subroutine psb_file_prec_descr(iout,p) + use psb_base_mod integer, intent(in) :: iout type(psb_dprec_type), intent(in) :: p integer :: ilev @@ -134,6 +137,7 @@ contains end subroutine psb_file_prec_descr subroutine psb_zfile_prec_descr(iout,p) + use psb_base_mod integer, intent(in) :: iout type(psb_zprec_type), intent(in) :: p @@ -151,26 +155,15 @@ contains function is_legal_prec(ip) + use psb_base_mod integer, intent(in) :: ip logical :: is_legal_prec is_legal_prec = ((ip>=noprec_).and.(ip<=bjac_)) return end function is_legal_prec - function is_legal_renum(ip) - integer, intent(in) :: ip - logical :: is_legal_renum - ! For the time being we are disabling renumbering options. - is_legal_renum = (ip ==0) - return - end function is_legal_renum - function is_legal_jac_sweeps(ip) - integer, intent(in) :: ip - logical :: is_legal_jac_sweeps - is_legal_jac_sweeps = (ip >= 1) - return - end function is_legal_jac_sweeps function is_legal_ml_fact(ip) + use psb_base_mod integer, intent(in) :: ip logical :: is_legal_ml_fact @@ -178,6 +171,7 @@ contains return end function is_legal_ml_fact function is_legal_ml_eps(ip) + use psb_base_mod real(kind(1.d0)), intent(in) :: ip logical :: is_legal_ml_eps @@ -187,6 +181,7 @@ contains subroutine psb_icheck_def(ip,name,id,is_legal) + use psb_base_mod integer, intent(inout) :: ip integer, intent(in) :: id character(len=*), intent(in) :: name @@ -204,6 +199,7 @@ contains end subroutine psb_icheck_def subroutine psb_dcheck_def(ip,name,id,is_legal) + use psb_base_mod real(kind(1.d0)), intent(inout) :: ip real(kind(1.d0)), intent(in) :: id character(len=*), intent(in) :: name @@ -286,6 +282,7 @@ contains end subroutine psb_d_precfree subroutine psb_nullify_dprec(p) + use psb_base_mod type(psb_dprec_type), intent(inout) :: p !!$ nullify(p%av,p%d,p%iprcparm,p%dprcparm,p%perm,p%invperm,p%mlia,& @@ -352,6 +349,7 @@ contains end subroutine psb_z_precfree subroutine psb_nullify_zprec(p) + use psb_base_mod type(psb_zprec_type), intent(inout) :: p @@ -359,6 +357,7 @@ contains function pr_to_str(iprec) + use psb_base_mod integer, intent(in) :: iprec character(len=10) :: pr_to_str diff --git a/prec/psb_zbjac_aply.f90 b/prec/psb_zbjac_aply.f90 index 108e1aae..25131ea1 100644 --- a/prec/psb_zbjac_aply.f90 +++ b/prec/psb_zbjac_aply.f90 @@ -37,7 +37,7 @@ subroutine psb_zbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) ! use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_zbjac_aply implicit none type(psb_desc_type), intent(in) :: desc_data @@ -100,90 +100,39 @@ subroutine psb_zbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) endif - if (prec%iprcparm(jac_sweeps_) == 1) then - select case(prec%iprcparm(f_type_)) - case(f_ilu_n_,f_ilu_e_) - - select case(trans) - case('N','n') - - call psb_spsm(zone,prec%av(l_pr_),x,zzero,ww,desc_data,info,& - & trans='N',unit=diagl,choice=psb_none_,work=aux) - if(info /=0) goto 9999 - ww(1:n_row) = ww(1:n_row)*prec%d(1:n_row) - call psb_spsm(alpha,prec%av(u_pr_),ww,beta,y,desc_data,info,& - & trans='N',unit=diagu,choice=psb_none_, work=aux) - if(info /=0) goto 9999 - - case('T','t','C','c') - call psb_spsm(zone,prec%av(u_pr_),x,zzero,ww,desc_data,info,& - & trans=trans,unit=diagu,choice=psb_none_, work=aux) - if(info /=0) goto 9999 - ww(1:n_row) = ww(1:n_row)*prec%d(1:n_row) - call psb_spsm(alpha,prec%av(l_pr_),ww,beta,y,desc_data,info,& - & trans=trans,unit=diagl,choice=psb_none_,work=aux) - if(info /=0) goto 9999 - - end select - - - case default - write(0,*) 'Unknown factorization type in bjac_aply',prec%iprcparm(f_type_) - end select - if (debugprt) write(0,*)' Y: ',y(:) - - else if (prec%iprcparm(jac_sweeps_) > 1) then - - ! Note: we have to add TRANS to this one !!!!!!!!! - - if (size(prec%av) < ap_nd_) then - info = 4011 - goto 9999 - endif - - allocate(tx(n_col),ty(n_col),stat=info) - if (info /= 0) then - call psb_errpush(4010,name,a_err='Allocate') - goto 9999 - end if - - tx = zzero - ty = zzero - select case(prec%iprcparm(f_type_)) - case(f_ilu_n_,f_ilu_e_) - do i=1, prec%iprcparm(jac_sweeps_) - ! X(k+1) = M^-1*(b-N*X(k)) - ty(1:n_row) = x(1:n_row) - call psb_spmm(-zone,prec%av(ap_nd_),tx,zone,ty,& - & prec%desc_data,info,work=aux) - if(info /=0) goto 9999 - call psb_spsm(zone,prec%av(l_pr_),ty,zzero,ww,& - & prec%desc_data,info,& - & trans='N',unit='U',choice=psb_none_,work=aux) - if(info /=0) goto 9999 - ww(1:n_row) = ww(1:n_row)*prec%d(1:n_row) - call psb_spsm(zone,prec%av(u_pr_),ww,zzero,tx,& - & prec%desc_data,info,& - & trans='N',unit='U',choice=psb_none_,work=aux) - if(info /=0) goto 9999 - end do - + select case(prec%iprcparm(f_type_)) + case(f_ilu_n_,f_ilu_e_) + + select case(trans) + case('N','n') + + call psb_spsm(zone,prec%av(l_pr_),x,zzero,ww,desc_data,info,& + & trans='N',unit=diagl,choice=psb_none_,work=aux) + if(info /=0) goto 9999 + ww(1:n_row) = ww(1:n_row)*prec%d(1:n_row) + call psb_spsm(alpha,prec%av(u_pr_),ww,beta,y,desc_data,info,& + & trans='N',unit=diagu,choice=psb_none_, work=aux) + if(info /=0) goto 9999 + + case('T','t','C','c') + call psb_spsm(zone,prec%av(u_pr_),x,zzero,ww,desc_data,info,& + & trans=trans,unit=diagu,choice=psb_none_, work=aux) + if(info /=0) goto 9999 + ww(1:n_row) = ww(1:n_row)*prec%d(1:n_row) + call psb_spsm(alpha,prec%av(l_pr_),ww,beta,y,desc_data,info,& + & trans=trans,unit=diagl,choice=psb_none_,work=aux) + if(info /=0) goto 9999 + end select - call psb_geaxpby(alpha,tx,beta,y,desc_data,info) - - deallocate(tx,ty) - - - else - - goto 9999 - - endif - + case default + write(0,*) 'Unknown factorization type in bjac_aply',prec%iprcparm(f_type_) + end select + if (debugprt) write(0,*)' Y: ',y(:) + if (n_col <= size(work)) then if ((4*n_col+n_col) <= size(work)) then else diff --git a/prec/psb_zdiagsc_bld.f90 b/prec/psb_zdiagsc_bld.f90 index 1085c0dd..51c3984a 100644 --- a/prec/psb_zdiagsc_bld.f90 +++ b/prec/psb_zdiagsc_bld.f90 @@ -31,7 +31,7 @@ subroutine psb_zdiagsc_bld(a,desc_a,p,upd,info) use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_zdiagsc_bld Implicit None type(psb_zspmat_type), target :: a diff --git a/prec/psb_zgprec_aply.f90 b/prec/psb_zgprec_aply.f90 index c4a1d130..8dd72a10 100644 --- a/prec/psb_zgprec_aply.f90 +++ b/prec/psb_zgprec_aply.f90 @@ -35,7 +35,7 @@ subroutine psb_zgprec_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) ! use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_zgprec_aply implicit none type(psb_desc_type),intent(in) :: desc_data @@ -55,21 +55,8 @@ subroutine psb_zgprec_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) logical,parameter :: debug=.false., debugprt=.false. character(len=20) :: name, ch_err - interface psb_bjac_aply - subroutine psb_zbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) - use psb_base_mod - use psb_prec_type - type(psb_desc_type), intent(in) :: desc_data - type(psb_zprec_type), intent(in) :: prec - complex(kind(0.d0)),intent(inout) :: x(:), y(:) - complex(kind(0.d0)),intent(in) :: alpha,beta - character(len=1) :: trans - complex(kind(0.d0)),target :: work(:) - integer, intent(out) :: info - end subroutine psb_zbjac_aply - end interface - - name='psb_baseprc_aply' + + name='psb_zgprec_aply' info = 0 call psb_erractionsave(err_act) diff --git a/prec/psb_zilu_bld.f90 b/prec/psb_zilu_bld.f90 index 04e3e097..152b70bd 100644 --- a/prec/psb_zilu_bld.f90 +++ b/prec/psb_zilu_bld.f90 @@ -30,7 +30,7 @@ !!$ subroutine psb_zilu_bld(a,desc_a,p,upd,info) use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_zilu_bld implicit none ! ! .. Scalar Arguments .. @@ -53,35 +53,10 @@ subroutine psb_zilu_bld(a,desc_a,p,upd,info) integer :: ictxt,np,me character(len=20) :: name, ch_err - interface psb_ilu_fct - subroutine psb_zilu_fct(a,l,u,d,info,blck) - use psb_base_mod - integer, intent(out) :: info - type(psb_zspmat_type),intent(in) :: a - type(psb_zspmat_type),intent(inout) :: l,u - type(psb_zspmat_type),intent(in), optional, target :: blck - complex(kind(1.d0)), intent(inout) :: d(:) - end subroutine psb_zilu_fct - end interface - - interface psb_sp_renum - subroutine psb_zsp_renum(a,desc_a,p,atmp,info) - use psb_base_mod - use psb_prec_type - implicit none - - ! .. array Arguments .. - type(psb_zspmat_type), intent(in) :: a - type(psb_zspmat_type), intent(inout) :: atmp - type(psb_zprec_type), intent(inout) :: p - type(psb_desc_type), intent(in) :: desc_a - integer, intent(out) :: info - end subroutine psb_zsp_renum - end interface if(psb_get_errstatus().ne.0) return info=0 - name='psb_ilu_bld' + name='psb_zilu_bld' call psb_erractionsave(err_act) ictxt=psb_cd_get_context(desc_a) @@ -145,90 +120,29 @@ subroutine psb_zilu_bld(a,desc_a,p,upd,info) endif - if (p%iprcparm(iren_) > 0) then - - ! - ! Here we allocate a full copy to hold local A and received BLK - ! - - nztota = psb_sp_get_nnzeros(a) - call psb_sp_all(atmp,nztota,info) - if(info/=0) then - info=4011 - call psb_errpush(info,name) - goto 9999 - end if - - - ! write(0,*) 'ILU_BLD ',nztota,nztotb,a%m - - call psb_sp_renum(a,desc_a,p,atmp,info) - - if(info/=0) then - info=4010 - ch_err='psb_sp_renum' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - - t3 = psb_wtime() - if (debugprt) then - call psb_barrier(ictxt) - open(40+me) - call psb_csprt(40+me,atmp,head='% Local matrix') - close(40+me) - endif - if (debug) write(0,*) me,' Factoring rows ',& - &atmp%m,a%m,atmp%ia2(atmp%m+1)-1 - - ! - ! Ok, factor the matrix. - ! - t5 = psb_wtime() - blck%m=0 - call psb_ilu_fct(atmp,p%av(l_pr_),p%av(u_pr_),p%d,info) - if(info/=0) then - info=4010 - ch_err='psb_ilu_fct' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - - call psb_sp_free(atmp,info) - if(info/=0) then - info=4010 - ch_err='psb_sp_free' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - - - else if (p%iprcparm(iren_) == 0) then - t3 = psb_wtime() - ! This is where we have mo renumbering, thus no need - ! for ATMP - - if (debugprt) then - open(40+me) - call psb_barrier(ictxt) - call psb_csprt(40+me,a,iv=p%desc_data%loc_to_glob,& - & head='% Local matrix') - close(40+me) - endif + t3 = psb_wtime() + ! This is where we have mo renumbering, thus no need + ! for ATMP - t5= psb_wtime() - if (debug) write(0,*) me,' Going for ilu_fct' - if (debug) call psb_barrier(ictxt) - call psb_ilu_fct(a,p%av(l_pr_),p%av(u_pr_),p%d,info) - if(info/=0) then - info=4010 - ch_err='psb_ilu_fct' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - if (debug) write(0,*) me,' Done dilu_fct' + if (debugprt) then + open(40+me) + call psb_barrier(ictxt) + call psb_csprt(40+me,a,iv=p%desc_data%loc_to_glob,& + & head='% Local matrix') + close(40+me) endif + t5= psb_wtime() + if (debug) write(0,*) me,' Going for ilu_fct' + if (debug) call psb_barrier(ictxt) + call psb_ilu_fct(a,p%av(l_pr_),p%av(u_pr_),p%d,info) + if(info/=0) then + info=4010 + ch_err='psb_ilu_fct' + call psb_errpush(info,name,a_err=ch_err) + goto 9999 + end if + if (debug) write(0,*) me,' Done dilu_fct' if (debugprt) then ! diff --git a/prec/psb_zprc_aply.f90 b/prec/psb_zprc_aply.f90 index 6e490a98..255aa872 100644 --- a/prec/psb_zprc_aply.f90 +++ b/prec/psb_zprc_aply.f90 @@ -31,7 +31,8 @@ subroutine psb_zprc_aply(prec,x,y,desc_data,info,trans, work) use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_zprc_aply + implicit none type(psb_desc_type),intent(in) :: desc_data @@ -48,21 +49,7 @@ subroutine psb_zprc_aply(prec,x,y,desc_data,info,trans, work) logical,parameter :: debug=.false., debugprt=.false. character(len=20) :: name - interface psb_gprec_aply - subroutine psb_zgprec_aply(alpha,prec,x,beta,y,desc_data,trans,work,info) - use psb_base_mod - use psb_prec_type - type(psb_desc_type),intent(in) :: desc_data - type(psb_zprec_type), intent(in) :: prec - complex(kind(0.d0)),intent(inout) :: x(:), y(:) - complex(kind(0.d0)),intent(in) :: alpha,beta - character(len=1) :: trans - complex(kind(0.d0)),target :: work(:) - integer, intent(out) :: info - end subroutine psb_zgprec_aply - end interface - - name='psb_prc_aply' + name='psb_zprec_aply' info = 0 call psb_erractionsave(err_act) @@ -146,7 +133,7 @@ end subroutine psb_zprc_aply subroutine psb_zprc_aply1(prec,x,desc_data,info,trans) use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_zprc_aply1 implicit none type(psb_desc_type),intent(in) :: desc_data @@ -156,22 +143,6 @@ subroutine psb_zprc_aply1(prec,x,desc_data,info,trans) character(len=1), optional :: trans logical,parameter :: debug=.false., debugprt=.false. - interface - subroutine psb_zprc_aply(prec,x,y,desc_data,info,trans, work) - - use psb_base_mod - use psb_prec_type - implicit none - - type(psb_desc_type),intent(in) :: desc_data - type(psb_zprec_type), intent(in) :: prec - complex(kind(0.d0)),intent(inout) :: x(:), y(:) - integer, intent(out) :: info - character(len=1), optional :: trans - complex(kind(0.d0)), optional, target :: work(:) - end subroutine psb_zprc_aply - end interface - ! Local variables character :: trans_ integer :: ictxt,np,me,i, isz, err_act, int_err(5) diff --git a/prec/psb_zprecbld.f90 b/prec/psb_zprecbld.f90 index 3fdde932..ae26a596 100644 --- a/prec/psb_zprecbld.f90 +++ b/prec/psb_zprecbld.f90 @@ -31,7 +31,7 @@ subroutine psb_zprecbld(a,desc_a,p,info,upd) use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_zprecbld Implicit None type(psb_zspmat_type), target :: a @@ -43,31 +43,6 @@ subroutine psb_zprecbld(a,desc_a,p,info,upd) ! Local scalars - interface psb_diagsc_bld - subroutine psb_zdiagsc_bld(a,desc_data,p,upd,info) - use psb_base_mod - use psb_prec_type - integer, intent(out) :: info - type(psb_zspmat_type), intent(in), target :: a - type(psb_desc_type),intent(in) :: desc_data - type(psb_zprec_type), intent(inout) :: p - character, intent(in) :: upd - end subroutine psb_zdiagsc_bld - end interface - - interface psb_ilu_bld - subroutine psb_zilu_bld(a,desc_data,p,upd,info) - use psb_base_mod - use psb_prec_type - integer, intent(out) :: info - type(psb_zspmat_type), intent(in), target :: a - type(psb_desc_type),intent(in) :: desc_data - type(psb_zprec_type), intent(inout) :: p - character, intent(in) :: upd - end subroutine psb_zilu_bld - end interface - - ! Local scalars Integer :: err, nnzero, n_row, n_col,I,j,k,ictxt,& & me,mycol,np,npcol,mglob,lw, mtype, nrg, nzg, err_act real(kind(1.d0)) :: temp, real_err(5) @@ -142,8 +117,6 @@ subroutine psb_zprecbld(a,desc_a,p,info,upd) case (bjac_) - call psb_check_def(p%iprcparm(iren_),'renumbering',& - & renum_none_,is_legal_renum) call psb_check_def(p%iprcparm(f_type_),'fact',& & f_ilu_n_,is_legal_ml_fact) diff --git a/prec/psb_zprecset.f90 b/prec/psb_zprecset.f90 index f5f48851..51b5919c 100644 --- a/prec/psb_zprecset.f90 +++ b/prec/psb_zprecset.f90 @@ -31,7 +31,7 @@ subroutine psb_zprecset(p,ptype,info,iv,rs,rv) use psb_base_mod - use psb_prec_type + use psb_prec_mod, psb_protect_name => psb_zprecset implicit none type(psb_zprec_type), intent(inout) :: p @@ -57,23 +57,17 @@ subroutine psb_zprecset(p,ptype,info,iv,rs,rv) p%iprcparm(:) = 0 p%iprcparm(p_type_) = noprec_ p%iprcparm(f_type_) = f_none_ - p%iprcparm(iren_) = 0 - p%iprcparm(jac_sweeps_) = 1 case ('DIAG') p%iprcparm(:) = 0 p%iprcparm(p_type_) = diag_ p%iprcparm(f_type_) = f_none_ - p%iprcparm(iren_) = 0 - p%iprcparm(jac_sweeps_) = 1 case ('BJAC') p%iprcparm(:) = 0 p%iprcparm(p_type_) = bjac_ p%iprcparm(f_type_) = f_ilu_n_ - p%iprcparm(iren_) = 0 p%iprcparm(ilu_fill_in_) = 0 - p%iprcparm(jac_sweeps_) = 1 case default write(0,*) 'Unknown preconditioner type request "',ptype,'"' diff --git a/prec/psb_zsp_renum.f90 b/prec/psb_zsp_renum.f90 deleted file mode 100644 index 5ee89564..00000000 --- a/prec/psb_zsp_renum.f90 +++ /dev/null @@ -1,388 +0,0 @@ -!!$ -!!$ Parallel Sparse BLAS v2.0 -!!$ (C) Copyright 2006 Salvatore Filippone University of Rome Tor Vergata -!!$ Alfredo Buttari University of Rome Tor Vergata -!!$ -!!$ Redistribution and use in source and binary forms, with or without -!!$ modification, are permitted provided that the following conditions -!!$ are met: -!!$ 1. Redistributions of source code must retain the above copyright -!!$ notice, this list of conditions and the following disclaimer. -!!$ 2. Redistributions in binary form must reproduce the above copyright -!!$ notice, this list of conditions, and the following disclaimer in the -!!$ documentation and/or other materials provided with the distribution. -!!$ 3. The name of the PSBLAS group or the names of its contributors may -!!$ not be used to endorse or promote products derived from this -!!$ software without specific written permission. -!!$ -!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -!!$ PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS -!!$ BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -!!$ CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -!!$ SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -!!$ INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -!!$ POSSIBILITY OF SUCH DAMAGE. -!!$ -!!$ -subroutine psb_zsp_renum(a,desc_a,p,atmp,info) - use psb_base_mod - use psb_prec_type - implicit none - - ! .. array Arguments .. - type(psb_zspmat_type), intent(in) :: a - type(psb_zspmat_type), intent(inout) :: atmp - type(psb_zprec_type), intent(inout) :: p - type(psb_desc_type), intent(in) :: desc_a - integer, intent(out) :: info - - - character(len=20) :: name, ch_err - integer nztota, nztotb, nztmp, nzl, nnr, ir, mglob, mtype, n_row, & - & nrow_a,n_col, nhalo,lovr, ind, iind, pi,nr,ns,i,j,jj,k,kk - integer ::ictxt,np,me, err_act - integer, allocatable :: itmp(:), itmp2(:) - complex(kind(1.d0)), allocatable :: ztmp(:) - real(kind(1.d0)) :: t1,t2,t3,t4,t5,t6, t7, t8 - - if (psb_get_errstatus().ne.0) return - info=0 - name='apply_renum' - call psb_erractionsave(err_act) - - ictxt=psb_cd_get_context(desc_a) - call psb_info(ictxt, me, np) - -!!!!!!!!!!!!!!!! CHANGE FOR NON-CSR A - ! - ! Renumbering type: - ! 1. Global column indices - ! (2. GPS band reduction disabled for the time being) - - if (p%iprcparm(iren_)==renum_glb_) then - atmp%m = a%m - atmp%k = a%k - atmp%fida='CSR' - atmp%descra = 'GUN' - - ! This is the renumbering coherent with global indices.. - mglob = psb_cd_get_global_rows(desc_a) - ! - ! Remember: we have switched IA1=COLS and IA2=ROWS - ! Now identify the set of distinct local column indices - ! - - nnr = p%desc_data%matrix_data(psb_n_row_) - allocate(p%perm(nnr),p%invperm(nnr),itmp2(nnr),stat=info) - if (info /= 0) then - call psb_errpush(4010,name,a_err='Allocate') - goto 9999 - end if - - do k=1,nnr - itmp2(k) = p%desc_data%loc_to_glob(k) - enddo - ! - ! We want: NEW(I) = OLD(PERM(I)) - ! - call psb_msort(itmp2(1:nnr),ix=p%perm) - - do k=1, nnr - p%invperm(p%perm(k)) = k - enddo - t3 = psb_wtime() - - ! Build ATMP with new numbering. - nztmp=size(atmp%aspk) - allocate(itmp(max(8,atmp%m+2,nztmp+2)),ztmp(atmp%m),stat=info) - if (info /= 0) then - call psb_errpush(4010,name,a_err='Allocate') - goto 9999 - end if - - j = 1 - atmp%ia2(1) = 1 - do i=1, atmp%m - ir = p%perm(i) - - if (ir <= a%m ) then - - nzl = a%ia2(ir+1) - a%ia2(ir) - if (nzl > size(ztmp)) then - call psb_realloc(nzl,ztmp,info) - if(info/=0) then - info=4010 - ch_err='psb_realloc' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - endif - jj = a%ia2(ir) - k=0 - do kk=1, nzl - if (a%ia1(jj+kk-1)<=atmp%m) then - k = k + 1 - ztmp(k) = a%aspk(jj+kk-1) - atmp%ia1(j+k-1) = p%invperm(a%ia1(jj+kk-1)) - endif - enddo - call psb_msort(atmp%ia1(j:j+k-1),ix=itmp2) - do kk=1,k - atmp%aspk(j+kk-1) = ztmp(itmp2(kk)) - enddo - - else - write(0,*) 'Row index error 1 :',i,ir - endif - - j = j + k - atmp%ia2(i+1) = j - - enddo - - t4 = psb_wtime() - - - deallocate(itmp,itmp2,ztmp) - - else if (p%iprcparm(iren_)==renum_gps_) then - - atmp%m = a%m - atmp%k = a%k - atmp%fida='CSR' - atmp%descra = 'GUN' - do i=1, a%m - atmp%ia2(i) = a%ia2(i) - do j= a%ia2(i), a%ia2(i+1)-1 - atmp%ia1(j) = a%ia1(j) - enddo - enddo - atmp%ia2(a%m+1) = a%ia2(a%m+1) - nztmp = atmp%ia2(atmp%m+1) - 1 - - - ! This is a renumbering with Gibbs-Poole-Stockmeyer - ! band reduction. Switched off for now. To be fixed, - ! gps_reduction should get p%perm. - - ! write(0,*) me,' Renumbering: realloc perms',atmp%m - call psb_realloc(atmp%m,p%perm,info) - if(info/=0) then - info=4010 - ch_err='psb_realloc' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - - call psb_realloc(atmp%m,p%invperm,info) - if(info/=0) then - info=4010 - ch_err='psb_realloc' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - - allocate(itmp(max(8,atmp%m+2,nztmp+2)),stat=info) - if (info /= 0) then - call psb_errpush(4010,name,a_err='Allocate') - goto 9999 - end if - - itmp(1:8) = 0 - ! write(0,*) me,' Renumbering: Calling Metis' - - ! write(0,*) size(p%av(u_pr_)%pl),size(p%av(l_pr_)%pr) - call gps_reduction(atmp%m,atmp%ia2,atmp%ia1,p%perm,p%invperm,info) - if(info/=0) then - info=4010 - ch_err='gps_reduction' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - - ! write(0,*) me,' Renumbering: Done GPS' - ! call psb_barrier(ictxt) - do i=1, atmp%m - if (p%perm(i) /= i) then - write(0,*) me,' permutation is not identity ' - exit - endif - enddo - - - - do k=1, nnr - p%invperm(p%perm(k)) = k - enddo - t3 = psb_wtime() - - ! Build ATMP with new numbering. - - allocate(itmp2(max(8,atmp%m+2,nztmp+2)),ztmp(atmp%m),stat=info) - if (info /= 0) then - call psb_errpush(4010,name,a_err='Allocate') - goto 9999 - end if - - j = 1 - atmp%ia2(1) = 1 - do i=1, atmp%m - ir = p%perm(i) - - if (ir <= a%m ) then - - nzl = a%ia2(ir+1) - a%ia2(ir) - if (nzl > size(ztmp)) then - call psb_realloc(nzl,ztmp,info) - if(info/=0) then - info=4010 - ch_err='psb_realloc' - call psb_errpush(info,name,a_err=ch_err) - goto 9999 - end if - endif - jj = a%ia2(ir) - k=0 - do kk=1, nzl - if (a%ia1(jj+kk-1)<=atmp%m) then - k = k + 1 - ztmp(k) = a%aspk(jj+kk-1) - atmp%ia1(j+k-1) = p%invperm(a%ia1(jj+kk-1)) - endif - enddo - call psb_msort(atmp%ia1(j:j+k-1),ix=itmp2) - do kk=1,k - atmp%aspk(j+kk-1) = ztmp(itmp2(kk)) - enddo - - else - write(0,*) 'Row index error 1 :',i,ir - endif - - j = j + k - atmp%ia2(i+1) = j - - enddo - - t4 = psb_wtime() - - - - deallocate(itmp,itmp2,ztmp) - - end if - - call psb_erractionrestore(err_act) - return - -9999 continue - call psb_erractionrestore(err_act) - if (err_act.eq.psb_act_abort_) then - call psb_error() - return - end if - return - -contains - - - subroutine gps_reduction(m,ia,ja,perm,iperm,info) - integer i,j,dgConn,Npnt,m - integer n,idpth,ideg,ibw2,ipf2 - integer,dimension(:) :: perm,iperm,ia,ja - integer, intent(out) :: info - - integer,dimension(:,:),allocatable::NDstk - integer,dimension(:),allocatable::iOld,renum,ndeg,lvl,lvls1,lvls2,ccstor - !--- Per la common area. - - character(len=20) :: name, ch_err - - if(psb_get_errstatus().ne.0) return - info=0 - name='gps_reduction' - call psb_erractionsave(err_act) - - - !--- Calcolo il massimo grado di connettivita'. - npnt = m - write(6,*) ' GPS su ',npnt - dgConn=0 - do i=1,m - dgconn = max(dgconn,(ia(i+1)-ia(i))) - enddo - !--- Il max valore di connettivita' e "dgConn" - - !--- Valori della common - n=Npnt !--- Numero di righe - iDeg=dgConn !--- Massima connettivita' - ! iDpth= !--- Numero di livelli non serve settarlo - - allocate(NDstk(Npnt,dgConn),stat=info) - if (info/=0) then - info=4000 - call psb_errpush(info,name) - goto 9999 - else - write(0,*) 'gps_reduction first alloc OK' - endif - allocate(iOld(Npnt),renum(Npnt+1),ndeg(Npnt),lvl(Npnt),lvls1(Npnt),& - &lvls2(Npnt),ccstor(Npnt),stat=info) - if (info/=0) then - info=4000 - call psb_errpush(info,name) - goto 9999 - else - write(0,*) 'gps_reduction 2nd alloc OK' - endif - - !--- Prepariamo il grafo della matrice - Ndstk(:,:)=0 - do i=1,Npnt - k=0 - do j = ia(i),ia(i+1) - 1 - if ((1<=ja(j)).and.( ja( j ) /= i ).and.(ja(j)<=npnt)) then - k = k+1 - Ndstk(i,k)=ja(j) - endif - enddo - ndeg(i)=k - enddo - - !--- Numerazione. - do i=1,Npnt - iOld(i)=i - enddo - write(0,*) 'gps_red : Preparation done' - !--- - !--- Chiamiamo funzione reduce. - call psb_gps_reduce(Ndstk,Npnt,iOld,renum,ndeg,lvl,lvls1, lvls2,ccstor,& - & ibw2,ipf2,n,idpth,ideg) - write(0,*) 'gps_red : Done reduce' - !--- Permutazione - perm(1:Npnt)=renum(1:Npnt) - !--- Inversa permutazione - do i=1,Npnt - iperm(perm(i))=i - enddo - !--- Puliamo tutto. - deallocate(NDstk,iOld,renum,ndeg,lvl,lvls1,lvls2,ccstor) - - call psb_erractionrestore(err_act) - return - -9999 continue - call psb_erractionrestore(err_act) - if (err_act.eq.psb_act_abort_) then - call psb_error() - return - end if - return - - end subroutine gps_reduction - -end subroutine psb_zsp_renum