Cleanup of variables flagedd by -Wunused.

stopcriterion
Salvatore Filippone 17 years ago
parent fe04944807
commit dedbbbe971

@ -122,9 +122,6 @@ subroutine mld_daggrmat_smth_asb(a,desc_a,ac,desc_ac,p,info)
type(psb_dspmat_type), pointer :: am1,am2 type(psb_dspmat_type), pointer :: am1,am2
type(psb_dspmat_type) :: am3,am4 type(psb_dspmat_type) :: am3,am4
logical :: ml_global_nmb logical :: ml_global_nmb
integer :: nz
integer, allocatable :: ia(:), ja(:)
real(kind(1.d0)), allocatable :: val(:)
integer :: debug_level, debug_unit integer :: debug_level, debug_unit
integer, parameter :: ncmax=16 integer, parameter :: ncmax=16
real(kind(1.d0)) :: omega, anorm, tmp, dg real(kind(1.d0)) :: omega, anorm, tmp, dg

@ -73,9 +73,8 @@ subroutine mld_das_bld(a,desc_a,p,upd,info)
! Local variables ! Local variables
integer :: ptype,novr integer :: ptype,novr
integer :: icomm integer :: icomm
Integer :: np,me,nnzero,& Integer :: np,me,nnzero,ictxt, int_err(5),&
& ictxt, n_col,int_err(5),& & tot_recv, n_row,n_col,nhalo, err_act, data_
& tot_recv, n_row,nhalo, nrow_a,err_act, data_
type(psb_dspmat_type) :: blck type(psb_dspmat_type) :: blck
integer :: debug_level, debug_unit integer :: debug_level, debug_unit
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
@ -97,10 +96,10 @@ subroutine mld_das_bld(a,desc_a,p,upd,info)
tot_recv=0 tot_recv=0
nrow_a = psb_cd_get_local_rows(desc_a) n_row = psb_cd_get_local_rows(desc_a)
n_col = psb_cd_get_local_cols(desc_a) n_col = psb_cd_get_local_cols(desc_a)
nnzero = psb_sp_get_nnzeros(a) nnzero = psb_sp_get_nnzeros(a)
nhalo = n_col-nrow_a nhalo = n_col-n_row
ptype = p%iprcparm(mld_prec_type_) ptype = p%iprcparm(mld_prec_type_)
novr = p%iprcparm(mld_n_ovr_) novr = p%iprcparm(mld_n_ovr_)

@ -94,9 +94,9 @@ subroutine mld_dbaseprec_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
integer, intent(out) :: info integer, intent(out) :: info
! Local variables ! Local variables
integer :: n_row,n_col, int_err(5), nrow_d real(kind(1.d0)), pointer :: ww(:)
real(kind(1.d0)), pointer :: ww(:), aux(:), tx(:),ty(:) integer :: ictxt, np, me, err_act
integer :: ictxt,np,me,isz, err_act integer :: n_row, int_err(5)
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
character :: trans_ character :: trans_

@ -111,14 +111,12 @@ subroutine mld_dbjac_bld(a,p,upd,info,blck)
type(psb_dspmat_type), intent(in), target, optional :: blck type(psb_dspmat_type), intent(in), target, optional :: blck
! Local Variables ! Local Variables
integer :: i, k, m
integer :: int_err(5)
character :: trans, unitd
type(psb_dspmat_type), pointer :: blck_ type(psb_dspmat_type), pointer :: blck_
type(psb_dspmat_type) :: atmp type(psb_dspmat_type) :: atmp
integer :: ictxt,np,me,err_act
integer :: debug_level, debug_unit integer :: debug_level, debug_unit
integer :: err_act, n_row, nrow_a,n_col integer :: k, m, int_err(5), n_row, nrow_a, n_col
integer :: ictxt,np,me character :: trans, unitd
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
if(psb_get_errstatus().ne.0) return if(psb_get_errstatus().ne.0) return

@ -372,7 +372,7 @@ contains
! need to keep track of fill levels for the upper triangle, hence we ! need to keep track of fill levels for the upper triangle, hence we
! do not have a lowlevs variable. ! do not have a lowlevs variable.
! !
if (info == 0) call iluk_fact(fill_in,i,m,row,rowlevs,heap,& if (info == 0) call iluk_fact(fill_in,i,row,rowlevs,heap,&
& d,uia1,uia2,uaspk,uplevs,nidx,idxs,info) & d,uia1,uia2,uaspk,uplevs,nidx,idxs,info)
! !
! Copy the row into laspk/d(i)/uaspk ! Copy the row into laspk/d(i)/uaspk
@ -589,9 +589,6 @@ contains
! i - integer, input. ! i - integer, input.
! The local index of the row to which the factorization is ! The local index of the row to which the factorization is
! applied. ! applied.
! m - integer, input.
! The number of rows of the local matrix to which the row
! belongs.
! row - real(kind(1.d0)), dimension(:), input/output. ! row - real(kind(1.d0)), dimension(:), input/output.
! In input it contains the row to which the elimination step ! In input it contains the row to which the elimination step
! has to be applied. In output it contains the row after the ! has to be applied. In output it contains the row after the
@ -639,7 +636,7 @@ contains
! Note: this argument is intent(inout) and not only intent(out) ! Note: this argument is intent(inout) and not only intent(out)
! to retain its allocation, done by this routine. ! to retain its allocation, done by this routine.
! !
subroutine iluk_fact(fill_in,i,m,row,rowlevs,heap,d,uia1,uia2,uaspk,uplevs,nidx,idxs,info) subroutine iluk_fact(fill_in,i,row,rowlevs,heap,d,uia1,uia2,uaspk,uplevs,nidx,idxs,info)
use psb_base_mod use psb_base_mod
@ -647,7 +644,7 @@ contains
! Arguments ! Arguments
type(psb_int_heap), intent(inout) :: heap type(psb_int_heap), intent(inout) :: heap
integer, intent(in) :: i,m, fill_in integer, intent(in) :: i, fill_in
integer, intent(inout) :: nidx,info integer, intent(inout) :: nidx,info
integer, intent(inout) :: rowlevs(:) integer, intent(inout) :: rowlevs(:)
integer, allocatable, intent(inout) :: idxs(:) integer, allocatable, intent(inout) :: idxs(:)

@ -351,7 +351,7 @@ contains
! !
! Do an elimination step on current row ! Do an elimination step on current row
! !
if (info == 0) call ilut_fact(fill_in,thres,i,m,nrmi,row,heap,& if (info == 0) call ilut_fact(thres,i,nrmi,row,heap,&
& d,uia1,uia2,uaspk,nidx,idxs,info) & d,uia1,uia2,uaspk,nidx,idxs,info)
! !
! Copy the row into laspk/d(i)/uaspk ! Copy the row into laspk/d(i)/uaspk
@ -492,7 +492,6 @@ contains
real(kind(1.d0)) :: dmaxup real(kind(1.d0)) :: dmaxup
real(kind(1.d0)), external :: dnrm2 real(kind(1.d0)), external :: dnrm2
character(len=20), parameter :: name='mld_dilut_fctint' character(len=20), parameter :: name='mld_dilut_fctint'
character(len=20) :: ch_err
if (psb_get_errstatus() /= 0) return if (psb_get_errstatus() /= 0) return
info = 0 info = 0
@ -622,14 +621,10 @@ contains
! !
! !
! Arguments ! Arguments
! fill_in - integer, input.
! The fill-in parameter k in ILU(k,t).
! thres - integer, input. ! thres - integer, input.
! The threshold t, i.e. the drop tolerance, in ILU(k,t). ! The threshold t, i.e. the drop tolerance, in ILU(k,t).
! i - integer, input. ! i - integer, input.
! The local index of the row to which the factorization is applied. ! The local index of the row to which the factorization is applied.
! m - integer, input.
! The number of rows of the local matrix to which the row belongs.
! nrmi - real(kind(1.d0)), input. ! nrmi - real(kind(1.d0)), input.
! The 2-norm of the row to which the elimination step has to be ! The 2-norm of the row to which the elimination step has to be
! applied. ! applied.
@ -671,7 +666,7 @@ contains
! Note: this argument is intent(inout) and not only intent(out) ! Note: this argument is intent(inout) and not only intent(out)
! to retain its allocation, done by this routine. ! to retain its allocation, done by this routine.
! !
subroutine ilut_fact(fill_in,thres,i,m,nrmi,row,heap,& subroutine ilut_fact(thres,i,nrmi,row,heap,&
& d,uia1,uia2,uaspk,nidx,idxs,info) & d,uia1,uia2,uaspk,nidx,idxs,info)
use psb_base_mod use psb_base_mod
@ -680,7 +675,7 @@ contains
! Arguments ! Arguments
type(psb_int_heap), intent(inout) :: heap type(psb_int_heap), intent(inout) :: heap
integer, intent(in) :: i,m,fill_in integer, intent(in) :: i
integer, intent(inout) :: nidx,info integer, intent(inout) :: nidx,info
real(kind(1.d0)), intent(in) :: thres,nrmi real(kind(1.d0)), intent(in) :: thres,nrmi
integer, allocatable, intent(inout) :: idxs(:) integer, allocatable, intent(inout) :: idxs(:)

@ -180,10 +180,8 @@ subroutine mld_dmlprec_aply(alpha,baseprecv,x,beta,y,desc_data,trans,work,info)
integer, intent(out) :: info integer, intent(out) :: info
! Local variables ! Local variables
integer :: n_row,n_col integer :: ictxt, np, me, err_act
integer :: ictxt,np,me,i, nr2l,nc2l,err_act
integer :: debug_level, debug_unit integer :: debug_level, debug_unit
integer :: ismth, nlev, ilev, icm
character(len=20) :: name character(len=20) :: name
character :: trans_ character :: trans_

@ -70,10 +70,9 @@ subroutine mld_dmlprec_bld(a,desc_a,p,info)
! Local variables ! Local variables
type(psb_desc_type) :: desc_ac type(psb_desc_type) :: desc_ac
integer :: err_act
character(len=20) :: name, ch_err
type(psb_dspmat_type) :: ac type(psb_dspmat_type) :: ac
integer :: ictxt, np, me character(len=20) :: name
integer :: ictxt, np, me, err_act
name='psb_dmlprec_bld' name='psb_dmlprec_bld'
if (psb_get_errstatus().ne.0) return if (psb_get_errstatus().ne.0) return

@ -94,9 +94,9 @@ subroutine mld_dsp_renum(a,blck,p,atmp,info)
! Local variables ! Local variables
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
integer nztota, nztotb, nztmp, nnr, mglob, i,k integer :: nztota, nztotb, nztmp, nnr, i,k
integer ::ictxt,np,me, err_act
integer, allocatable :: itmp(:), itmp2(:) integer, allocatable :: itmp(:), itmp2(:)
integer :: ictxt,np,me, err_act
real(kind(1.d0)) :: t3,t4 real(kind(1.d0)) :: t3,t4
if (psb_get_errstatus().ne.0) return if (psb_get_errstatus().ne.0) return

@ -122,9 +122,6 @@ subroutine mld_zaggrmat_smth_asb(a,desc_a,ac,desc_ac,p,info)
type(psb_zspmat_type), pointer :: am1,am2 type(psb_zspmat_type), pointer :: am1,am2
type(psb_zspmat_type) :: am3,am4 type(psb_zspmat_type) :: am3,am4
logical :: ml_global_nmb logical :: ml_global_nmb
integer :: nz
integer, allocatable :: ia(:), ja(:)
complex(kind(1.d0)), allocatable :: val(:)
integer :: debug_level, debug_unit integer :: debug_level, debug_unit
integer, parameter :: ncmax=16 integer, parameter :: ncmax=16
real(kind(1.d0)) :: omega, anorm, tmp, dg real(kind(1.d0)) :: omega, anorm, tmp, dg

@ -74,9 +74,8 @@ subroutine mld_zas_bld(a,desc_a,p,upd,info)
! Local variables ! Local variables
integer :: ptype,novr integer :: ptype,novr
integer :: icomm integer :: icomm
Integer :: np,me,nnzero,& Integer :: np,me,nnzero,ictxt, int_err(5),&
& ictxt, n_col,int_err(5),& & tot_recv, n_row,n_col,nhalo, err_act, data_
& tot_recv, n_row,nhalo, nrow_a,err_act, data_
type(psb_zspmat_type) :: blck type(psb_zspmat_type) :: blck
integer :: debug_level, debug_unit integer :: debug_level, debug_unit
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
@ -98,10 +97,10 @@ subroutine mld_zas_bld(a,desc_a,p,upd,info)
tot_recv=0 tot_recv=0
nrow_a = psb_cd_get_local_rows(desc_a) n_row = psb_cd_get_local_rows(desc_a)
n_col = psb_cd_get_local_cols(desc_a) n_col = psb_cd_get_local_cols(desc_a)
nnzero = psb_sp_get_nnzeros(a) nnzero = psb_sp_get_nnzeros(a)
nhalo = n_col-nrow_a nhalo = n_col-n_row
ptype = p%iprcparm(mld_prec_type_) ptype = p%iprcparm(mld_prec_type_)
novr = p%iprcparm(mld_n_ovr_) novr = p%iprcparm(mld_n_ovr_)

@ -94,9 +94,9 @@ subroutine mld_zbaseprec_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
integer, intent(out) :: info integer, intent(out) :: info
! Local variables ! Local variables
integer :: n_row,n_col, int_err(5), nrow_d complex(kind(1.d0)), pointer :: ww(:)
complex(kind(1.d0)), pointer :: ww(:), aux(:), tx(:),ty(:) integer :: ictxt, np, me, err_act
integer :: ictxt,np,me,isz, err_act integer :: n_row, int_err(5)
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
character :: trans_ character :: trans_

@ -111,14 +111,12 @@ subroutine mld_zbjac_bld(a,p,upd,info,blck)
type(psb_zspmat_type), intent(in), target, optional :: blck type(psb_zspmat_type), intent(in), target, optional :: blck
! Local Variables ! Local Variables
integer :: i, k, m
integer :: int_err(5)
character :: trans, unitd
type(psb_zspmat_type), pointer :: blck_ type(psb_zspmat_type), pointer :: blck_
type(psb_zspmat_type) :: atmp type(psb_zspmat_type) :: atmp
integer :: ictxt,np,me,err_act
integer :: debug_level, debug_unit integer :: debug_level, debug_unit
integer :: err_act, n_row, nrow_a,n_col integer :: k, m, int_err(5), n_row, nrow_a, n_col
integer :: ictxt,np,me character :: trans, unitd
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
if(psb_get_errstatus().ne.0) return if(psb_get_errstatus().ne.0) return

@ -371,7 +371,7 @@ contains
! need to keep track of fill levels for the upper triangle, hence we ! need to keep track of fill levels for the upper triangle, hence we
! do not have a lowlevs variable. ! do not have a lowlevs variable.
! !
if (info == 0) call iluk_fact(fill_in,i,m,row,rowlevs,heap,& if (info == 0) call iluk_fact(fill_in,i,row,rowlevs,heap,&
& d,uia1,uia2,uaspk,uplevs,nidx,idxs,info) & d,uia1,uia2,uaspk,uplevs,nidx,idxs,info)
! !
! Copy the row into laspk/d(i)/uaspk ! Copy the row into laspk/d(i)/uaspk
@ -588,9 +588,6 @@ contains
! i - integer, input. ! i - integer, input.
! The local index of the row to which the factorization is ! The local index of the row to which the factorization is
! applied. ! applied.
! m - integer, input.
! The number of rows of the local matrix to which the row
! belongs.
! row - complex(kind(1.d0)), dimension(:), input/output. ! row - complex(kind(1.d0)), dimension(:), input/output.
! In input it contains the row to which the elimination step ! In input it contains the row to which the elimination step
! has to be applied. In output it contains the row after the ! has to be applied. In output it contains the row after the
@ -638,7 +635,7 @@ contains
! Note: this argument is intent(inout) and not only intent(out) ! Note: this argument is intent(inout) and not only intent(out)
! to retain its allocation, done by this routine. ! to retain its allocation, done by this routine.
! !
subroutine iluk_fact(fill_in,i,m,row,rowlevs,heap,d,uia1,uia2,uaspk,uplevs,nidx,idxs,info) subroutine iluk_fact(fill_in,i,row,rowlevs,heap,d,uia1,uia2,uaspk,uplevs,nidx,idxs,info)
use psb_base_mod use psb_base_mod
@ -646,7 +643,7 @@ contains
! Arguments ! Arguments
type(psb_int_heap), intent(inout) :: heap type(psb_int_heap), intent(inout) :: heap
integer, intent(in) :: i,m, fill_in integer, intent(in) :: i, fill_in
integer, intent(inout) :: nidx,info integer, intent(inout) :: nidx,info
integer, intent(inout) :: rowlevs(:) integer, intent(inout) :: rowlevs(:)
integer, allocatable, intent(inout) :: idxs(:) integer, allocatable, intent(inout) :: idxs(:)

@ -286,7 +286,6 @@ contains
type(psb_int_heap) :: heap type(psb_int_heap) :: heap
type(psb_zspmat_type) :: trw type(psb_zspmat_type) :: trw
character(len=20), parameter :: name='mld_zilut_fctint' character(len=20), parameter :: name='mld_zilut_fctint'
character(len=20) :: ch_err
if (psb_get_errstatus() /= 0) return if (psb_get_errstatus() /= 0) return
info = 0 info = 0
@ -350,7 +349,7 @@ contains
! !
! Do an elimination step on current row ! Do an elimination step on current row
! !
if (info == 0) call ilut_fact(fill_in,thres,i,m,nrmi,row,heap,& if (info == 0) call ilut_fact(thres,i,nrmi,row,heap,&
& d,uia1,uia2,uaspk,nidx,idxs,info) & d,uia1,uia2,uaspk,nidx,idxs,info)
! !
! Copy the row into laspk/d(i)/uaspk ! Copy the row into laspk/d(i)/uaspk
@ -492,7 +491,6 @@ contains
real(kind(1.d0)) :: dmaxup real(kind(1.d0)) :: dmaxup
real(kind(1.d0)), external :: dznrm2 real(kind(1.d0)), external :: dznrm2
character(len=20), parameter :: name='mld_zilut_fctint' character(len=20), parameter :: name='mld_zilut_fctint'
character(len=20) :: ch_err
if (psb_get_errstatus() /= 0) return if (psb_get_errstatus() /= 0) return
info = 0 info = 0
@ -622,14 +620,10 @@ contains
! !
! !
! Arguments ! Arguments
! fill_in - integer, input.
! The fill-in parameter k in ILU(k,t).
! thres - integer, input. ! thres - integer, input.
! The threshold t, i.e. the drop tolerance, in ILU(k,t). ! The threshold t, i.e. the drop tolerance, in ILU(k,t).
! i - integer, input. ! i - integer, input.
! The local index of the row to which the factorization is applied. ! The local index of the row to which the factorization is applied.
! m - integer, input.
! The number of rows of the local matrix to which the row belongs.
! nrmi - real(kind(1.d0)), input. ! nrmi - real(kind(1.d0)), input.
! The 2-norm of the row to which the elimination step has to be ! The 2-norm of the row to which the elimination step has to be
! applied. ! applied.
@ -671,8 +665,7 @@ contains
! Note: this argument is intent(inout) and not only intent(out) ! Note: this argument is intent(inout) and not only intent(out)
! to retain its allocation, done by this routine. ! to retain its allocation, done by this routine.
! !
subroutine ilut_fact(fill_in,thres,i,m,nrmi,row,heap,& subroutine ilut_fact(thres,i,nrmi,row,heap,d,uia1,uia2,uaspk,nidx,idxs,info)
& d,uia1,uia2,uaspk,nidx,idxs,info)
use psb_base_mod use psb_base_mod
@ -680,7 +673,7 @@ contains
! Arguments ! Arguments
type(psb_int_heap), intent(inout) :: heap type(psb_int_heap), intent(inout) :: heap
integer, intent(in) :: i,m,fill_in integer, intent(in) :: i
integer, intent(inout) :: nidx,info integer, intent(inout) :: nidx,info
real(kind(1.d0)), intent(in) :: thres,nrmi real(kind(1.d0)), intent(in) :: thres,nrmi
integer, allocatable, intent(inout) :: idxs(:) integer, allocatable, intent(inout) :: idxs(:)

@ -180,10 +180,8 @@ subroutine mld_zmlprec_aply(alpha,baseprecv,x,beta,y,desc_data,trans,work,info)
integer, intent(out) :: info integer, intent(out) :: info
! Local variables ! Local variables
integer :: n_row,n_col integer :: ictxt, np, me, err_act
integer :: ictxt,np,me,i, nr2l,nc2l,err_act
integer :: debug_level, debug_unit integer :: debug_level, debug_unit
integer :: ismth, nlev, ilev, icm
character(len=20) :: name character(len=20) :: name
character :: trans_ character :: trans_

@ -70,10 +70,9 @@ subroutine mld_zmlprec_bld(a,desc_a,p,info)
! Local variables ! Local variables
type(psb_desc_type) :: desc_ac type(psb_desc_type) :: desc_ac
integer :: err_act
character(len=20) :: name, ch_err
type(psb_zspmat_type) :: ac type(psb_zspmat_type) :: ac
integer :: ictxt, np, me character(len=20) :: name
integer :: ictxt, np, me, err_act
name='psb_zmlprec_bld' name='psb_zmlprec_bld'
if (psb_get_errstatus().ne.0) return if (psb_get_errstatus().ne.0) return

@ -94,9 +94,9 @@ subroutine mld_zsp_renum(a,blck,p,atmp,info)
! Local variables ! Local variables
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
integer nztota, nztotb, nztmp, nnr, mglob, i,k integer :: nztota, nztotb, nztmp, nnr, i,k
integer ::ictxt,np,me, err_act
integer, allocatable :: itmp(:), itmp2(:) integer, allocatable :: itmp(:), itmp2(:)
integer :: ictxt,np,me, err_act
real(kind(1.d0)) :: t3,t4 real(kind(1.d0)) :: t3,t4
if (psb_get_errstatus().ne.0) return if (psb_get_errstatus().ne.0) return

Loading…
Cancel
Save