Take out obsolete refs to mpi_wtime, use psb_wtime instead.

stopcriterion
Salvatore Filippone 18 years ago
parent fe9b3e4aaf
commit 12b31cfdae

@ -68,8 +68,7 @@ Subroutine psb_dasmatbld(ptype,novr,a,blk,desc_data,upd,desc_p,info,outfmt)
character(len=5), optional :: outfmt character(len=5), optional :: outfmt
real(kind(1.d0)) :: t1,t2,t3,mpi_wtime real(kind(1.d0)) :: t1,t2,t3
external mpi_wtime
integer icomm integer icomm
! .. Local Scalars .. ! .. Local Scalars ..
@ -170,7 +169,7 @@ Subroutine psb_dasmatbld(ptype,novr,a,blk,desc_data,upd,desc_p,info,outfmt)
call psb_get_mpicomm(ictxt,icomm) call psb_get_mpicomm(ictxt,icomm)
If(debug)Write(0,*)'BEGIN dasmatbld',me,upd,novr If(debug)Write(0,*)'BEGIN dasmatbld',me,upd,novr
t1 = mpi_wtime() t1 = psb_wtime()
If (upd == 'F') Then If (upd == 'F') Then
! !
@ -190,7 +189,7 @@ Subroutine psb_dasmatbld(ptype,novr,a,blk,desc_data,upd,desc_p,info,outfmt)
n_row = desc_p%matrix_data(psb_n_row_) n_row = desc_p%matrix_data(psb_n_row_)
t2 = mpi_wtime() t2 = psb_wtime()
!!$ open(60+me) !!$ open(60+me)
!!$ call psb_cdprt(60+me,desc_p,short=.false.) !!$ call psb_cdprt(60+me,desc_p,short=.false.)
!!$ call flush(60+me) !!$ call flush(60+me)
@ -220,7 +219,7 @@ Subroutine psb_dasmatbld(ptype,novr,a,blk,desc_data,upd,desc_p,info,outfmt)
if (debug) write(0,*) 'After psb_sphalo ',blk%fida,blk%m,psb_nnz_,blk%infoa(psb_nnz_) if (debug) write(0,*) 'After psb_sphalo ',blk%fida,blk%m,psb_nnz_,blk%infoa(psb_nnz_)
!!$ ierr = MPE_Log_event( iovre, 0, "ed OVR" ) !!$ ierr = MPE_Log_event( iovre, 0, "ed OVR" )
t3 = mpi_wtime() t3 = psb_wtime()
if (debugprt) then if (debugprt) then
open(40+me) open(40+me)
call psb_csprt(40+me,blk,head='% Ovrlap rows') call psb_csprt(40+me,blk,head='% Ovrlap rows')

@ -57,9 +57,8 @@ subroutine psb_dbaseprc_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
real(kind(1.d0)), pointer :: ww(:), aux(:), tx(:),ty(:) real(kind(1.d0)), pointer :: ww(:), aux(:), tx(:),ty(:)
character ::diagl, diagu character ::diagl, diagu
integer :: ictxt,np,me,i, isz, nrg, err_act integer :: ictxt,np,me,i, isz, nrg, err_act
real(kind(1.d0)) :: t1, t2, t3, t4, t5, t6, t7, mpi_wtime real(kind(1.d0)) :: t1, t2, t3, t4, t5, t6, t7
logical,parameter :: debug=.false., debugprt=.false. logical,parameter :: debug=.false., debugprt=.false.
external mpi_wtime
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
interface psb_bjac_aply interface psb_bjac_aply

@ -59,9 +59,8 @@ subroutine psb_dbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
real(kind(1.d0)), pointer :: ww(:), aux(:), tx(:),ty(:),tb(:) real(kind(1.d0)), pointer :: ww(:), aux(:), tx(:),ty(:),tb(:)
character ::diagl, diagu character ::diagl, diagu
integer :: ictxt,np,me,i, nrg, err_act, int_err(5) integer :: ictxt,np,me,i, nrg, err_act, int_err(5)
real(kind(1.d0)) :: t1, t2, t3, t4, t5, t6, t7, mpi_wtime real(kind(1.d0)) :: t1, t2, t3, t4, t5, t6, t7
logical,parameter :: debug=.false., debugprt=.false. logical,parameter :: debug=.false., debugprt=.false.
external mpi_wtime
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
name='psb_bjac_aply' name='psb_bjac_aply'

@ -67,8 +67,7 @@ subroutine psb_dilu_bld(a,desc_a,p,upd,info)
integer :: int_err(5) integer :: int_err(5)
character :: trans, unitd character :: trans, unitd
type(psb_dspmat_type) :: blck, atmp type(psb_dspmat_type) :: blck, atmp
real(kind(1.d0)) :: t1,t2,t3,t4,t5,t6,mpi_wtime, t7, t8 real(kind(1.d0)) :: t1,t2,t3,t4,t5,t6, t7, t8
external mpi_wtime
logical, parameter :: debugprt=.false., debug=.false., aggr_dump=.false. logical, parameter :: debugprt=.false., debug=.false., aggr_dump=.false.
integer nztota, nztotb, nztmp, nzl, nnr, ir, err_act,& integer nztota, nztotb, nztmp, nzl, nnr, ir, err_act,&
& n_row, nrow_a,n_col, nhalo, ind, iind, i1,i2,ia & n_row, nrow_a,n_col, nhalo, ind, iind, i1,i2,ia
@ -143,7 +142,7 @@ subroutine psb_dilu_bld(a,desc_a,p,upd,info)
call psb_nullify_sp(blck) call psb_nullify_sp(blck)
call psb_nullify_sp(atmp) call psb_nullify_sp(atmp)
t1= mpi_wtime() t1= psb_wtime()
if(debug) write(0,*)me,': calling psb_asmatbld',p%iprcparm(p_type_),p%iprcparm(n_ovr_) if(debug) write(0,*)me,': calling psb_asmatbld',p%iprcparm(p_type_),p%iprcparm(n_ovr_)
if (debug) call psb_barrier(ictxt) if (debug) call psb_barrier(ictxt)
@ -155,7 +154,7 @@ subroutine psb_dilu_bld(a,desc_a,p,upd,info)
call psb_errpush(info,name,a_err=ch_err) call psb_errpush(info,name,a_err=ch_err)
goto 9999 goto 9999
end if end if
t2= mpi_wtime() t2= psb_wtime()
if (debug) write(0,*)me,': out of psb_asmatbld' if (debug) write(0,*)me,': out of psb_asmatbld'
if (debug) call psb_barrier(ictxt) if (debug) call psb_barrier(ictxt)
@ -240,7 +239,7 @@ subroutine psb_dilu_bld(a,desc_a,p,upd,info)
goto 9999 goto 9999
end if end if
t3 = mpi_wtime() t3 = psb_wtime()
if (debugprt) then if (debugprt) then
call psb_barrier(ictxt) call psb_barrier(ictxt)
open(40+me) open(40+me)
@ -253,7 +252,7 @@ subroutine psb_dilu_bld(a,desc_a,p,upd,info)
! !
! Ok, factor the matrix. ! Ok, factor the matrix.
! !
t5 = mpi_wtime() t5 = psb_wtime()
blck%m=0 blck%m=0
call psb_ilu_fct(atmp,p%av(l_pr_),p%av(u_pr_),p%d,info,blck=blck) call psb_ilu_fct(atmp,p%av(l_pr_),p%av(u_pr_),p%d,info,blck=blck)
if(info/=0) then if(info/=0) then
@ -273,7 +272,7 @@ subroutine psb_dilu_bld(a,desc_a,p,upd,info)
else if (p%iprcparm(iren_) == 0) then else if (p%iprcparm(iren_) == 0) then
t3 = mpi_wtime() t3 = psb_wtime()
! This is where we have mo renumbering, thus no need ! This is where we have mo renumbering, thus no need
! for ATMP ! for ATMP
@ -289,7 +288,7 @@ subroutine psb_dilu_bld(a,desc_a,p,upd,info)
close(40+me) close(40+me)
endif endif
t5= mpi_wtime() t5= psb_wtime()
if (debug) write(0,*) me,' Going for ilu_fct' if (debug) write(0,*) me,' Going for ilu_fct'
if (debug) call psb_barrier(ictxt) if (debug) call psb_barrier(ictxt)
call psb_ilu_fct(a,p%av(l_pr_),p%av(u_pr_),p%d,info,blck=blck) call psb_ilu_fct(a,p%av(l_pr_),p%av(u_pr_),p%d,info,blck=blck)
@ -323,7 +322,7 @@ subroutine psb_dilu_bld(a,desc_a,p,upd,info)
! ierr = MPE_Log_event( ifcte, 0, "st SIMPLE" ) ! ierr = MPE_Log_event( ifcte, 0, "st SIMPLE" )
t6 = mpi_wtime() t6 = psb_wtime()
! !
! write(0,'(i3,1x,a,3(1x,g18.9))') me,'renum/factor time',t3-t2,t6-t5 ! write(0,'(i3,1x,a,3(1x,g18.9))') me,'renum/factor time',t3-t2,t6-t5
! if (me==0) write(0,'(a,3(1x,g18.9))') 'renum/factor time',t3-t2,t6-t5 ! if (me==0) write(0,'(a,3(1x,g18.9))') 'renum/factor time',t3-t2,t6-t5

@ -102,10 +102,9 @@ subroutine psb_dmlprc_aply(alpha,baseprecv,x,beta,y,desc_data,trans,work,info)
character ::diagl, diagu character ::diagl, diagu
integer :: ictxt,np,me,i, isz, nrg,nr2l,err_act, iptype, int_err(5) integer :: ictxt,np,me,i, isz, nrg,nr2l,err_act, iptype, int_err(5)
real(kind(1.d0)) :: omega real(kind(1.d0)) :: omega
real(kind(1.d0)) :: t1, t2, t3, t4, t5, t6, t7, mpi_wtime real(kind(1.d0)) :: t1, t2, t3, t4, t5, t6, t7
logical, parameter :: debug=.false., debugprt=.false. logical, parameter :: debug=.false., debugprt=.false.
integer :: ismth, nlev, ilev integer :: ismth, nlev, ilev
external mpi_wtime
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
type psb_mlprec_wrk_type type psb_mlprec_wrk_type

@ -52,7 +52,6 @@ subroutine psb_dprc_aply(prec,x,y,desc_data,info,trans, work)
real(kind(1.d0)), pointer :: work_(:) real(kind(1.d0)), pointer :: work_(:)
integer :: ictxt,np,me,err_act integer :: ictxt,np,me,err_act
logical,parameter :: debug=.false., debugprt=.false. logical,parameter :: debug=.false., debugprt=.false.
external mpi_wtime
character(len=20) :: name character(len=20) :: name
interface psb_baseprc_aply interface psb_baseprc_aply

@ -53,8 +53,7 @@ subroutine psb_dsp_renum(a,desc_a,blck,p,atmp,info)
integer ::ictxt,np,me, err_act integer ::ictxt,np,me, err_act
integer, allocatable :: itmp(:), itmp2(:) integer, allocatable :: itmp(:), itmp2(:)
real(kind(1.d0)), allocatable :: rtmp(:) real(kind(1.d0)), allocatable :: rtmp(:)
real(kind(1.d0)) :: t1,t2,t3,t4,t5,t6,mpi_wtime, t7, t8 real(kind(1.d0)) :: t1,t2,t3,t4,t5,t6, t7, t8
external mpi_wtime
if (psb_get_errstatus().ne.0) return if (psb_get_errstatus().ne.0) return
info=0 info=0
@ -103,7 +102,7 @@ subroutine psb_dsp_renum(a,desc_a,blck,p,atmp,info)
do k=1, nnr do k=1, nnr
p%invperm(p%perm(k)) = k p%invperm(p%perm(k)) = k
enddo enddo
t3 = mpi_wtime() t3 = psb_wtime()
! Build ATMP with new numbering. ! Build ATMP with new numbering.
nztmp=size(atmp%aspk) nztmp=size(atmp%aspk)
@ -180,7 +179,7 @@ subroutine psb_dsp_renum(a,desc_a,blck,p,atmp,info)
enddo enddo
t4 = mpi_wtime() t4 = psb_wtime()
deallocate(itmp,itmp2,rtmp) deallocate(itmp,itmp2,rtmp)
@ -263,7 +262,7 @@ subroutine psb_dsp_renum(a,desc_a,blck,p,atmp,info)
do k=1, nnr do k=1, nnr
p%invperm(p%perm(k)) = k p%invperm(p%perm(k)) = k
enddo enddo
t3 = mpi_wtime() t3 = psb_wtime()
! Build ATMP with new numbering. ! Build ATMP with new numbering.
@ -340,7 +339,7 @@ subroutine psb_dsp_renum(a,desc_a,blck,p,atmp,info)
enddo enddo
t4 = mpi_wtime() t4 = psb_wtime()

@ -68,8 +68,7 @@ Subroutine psb_zasmatbld(ptype,novr,a,blk,desc_data,upd,desc_p,info,outfmt)
character(len=5), optional :: outfmt character(len=5), optional :: outfmt
real(kind(1.d0)) :: t1,t2,t3,mpi_wtime real(kind(1.d0)) :: t1,t2,t3
external mpi_wtime
integer icomm integer icomm
! .. Local Scalars .. ! .. Local Scalars ..
@ -170,7 +169,7 @@ Subroutine psb_zasmatbld(ptype,novr,a,blk,desc_data,upd,desc_p,info,outfmt)
Call psb_info(ictxt, me, np) Call psb_info(ictxt, me, np)
If(debug)Write(0,*)'BEGIN dasmatbld',me,upd,novr If(debug)Write(0,*)'BEGIN dasmatbld',me,upd,novr
t1 = mpi_wtime() t1 = psb_wtime()
If (upd == 'F') Then If (upd == 'F') Then
! !
@ -189,7 +188,7 @@ Subroutine psb_zasmatbld(ptype,novr,a,blk,desc_data,upd,desc_p,info,outfmt)
n_row = desc_p%matrix_data(psb_n_row_) n_row = desc_p%matrix_data(psb_n_row_)
t2 = mpi_wtime() t2 = psb_wtime()
if (debug) write(0,*) 'Before sphalo ',blk%fida,blk%m,psb_nnz_,blk%infoa(psb_nnz_) if (debug) write(0,*) 'Before sphalo ',blk%fida,blk%m,psb_nnz_,blk%infoa(psb_nnz_)
@ -211,7 +210,7 @@ Subroutine psb_zasmatbld(ptype,novr,a,blk,desc_data,upd,desc_p,info,outfmt)
if (debug) write(0,*) 'After psb_sphalo ',blk%fida,blk%m,psb_nnz_,blk%infoa(psb_nnz_) if (debug) write(0,*) 'After psb_sphalo ',blk%fida,blk%m,psb_nnz_,blk%infoa(psb_nnz_)
t3 = mpi_wtime() t3 = psb_wtime()
if (debugprt) then if (debugprt) then
open(40+me) open(40+me)
call psb_csprt(40+me,blk,head='% Ovrlap rows') call psb_csprt(40+me,blk,head='% Ovrlap rows')

@ -56,9 +56,8 @@ subroutine psb_zbaseprc_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
complex(kind(1.d0)), pointer :: ww(:), aux(:), tx(:),ty(:) complex(kind(1.d0)), pointer :: ww(:), aux(:), tx(:),ty(:)
character ::diagl, diagu character ::diagl, diagu
integer :: ictxt,np,me,i, isz, nrg, err_act integer :: ictxt,np,me,i, isz, nrg, err_act
real(kind(1.d0)) :: t1, t2, t3, t4, t5, t6, t7, mpi_wtime real(kind(1.d0)) :: t1, t2, t3, t4, t5, t6, t7
logical,parameter :: debug=.false., debugprt=.false. logical,parameter :: debug=.false., debugprt=.false.
external mpi_wtime
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
interface psb_bjac_aply interface psb_bjac_aply

@ -59,9 +59,8 @@ subroutine psb_zbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
complex(kind(1.d0)), pointer :: ww(:), aux(:), tx(:),ty(:),tb(:) complex(kind(1.d0)), pointer :: ww(:), aux(:), tx(:),ty(:),tb(:)
character ::diagl, diagu character ::diagl, diagu
integer :: ictxt,np,me,i, isz, nrg, err_act, int_err(5) integer :: ictxt,np,me,i, isz, nrg, err_act, int_err(5)
real(kind(1.d0)) :: t1, t2, t3, t4, t5, t6, t7, mpi_wtime real(kind(1.d0)) :: t1, t2, t3, t4, t5, t6, t7
logical,parameter :: debug=.false., debugprt=.false. logical,parameter :: debug=.false., debugprt=.false.
external mpi_wtime
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
name='psb_bjac_aply' name='psb_bjac_aply'

@ -67,8 +67,7 @@ subroutine psb_zilu_bld(a,desc_a,p,upd,info)
integer :: int_err(5) integer :: int_err(5)
character :: trans, unitd character :: trans, unitd
type(psb_zspmat_type) :: blck, atmp type(psb_zspmat_type) :: blck, atmp
real(kind(1.d0)) :: t1,t2,t3,t4,t5,t6,mpi_wtime, t7, t8 real(kind(1.d0)) :: t1,t2,t3,t4,t5,t6, t7, t8
external mpi_wtime
logical, parameter :: debugprt=.false., debug=.false., aggr_dump=.false. logical, parameter :: debugprt=.false., debug=.false., aggr_dump=.false.
integer nztota, nztotb, nztmp, nzl, nnr, ir, err_act,& integer nztota, nztotb, nztmp, nzl, nnr, ir, err_act,&
& n_row, nrow_a,n_col, nhalo, ind, iind, i1,i2,ia & n_row, nrow_a,n_col, nhalo, ind, iind, i1,i2,ia
@ -143,7 +142,7 @@ subroutine psb_zilu_bld(a,desc_a,p,upd,info)
call psb_nullify_sp(blck) call psb_nullify_sp(blck)
call psb_nullify_sp(atmp) call psb_nullify_sp(atmp)
t1= mpi_wtime() t1= psb_wtime()
if(debug) write(0,*)me,': calling psb_asmatbld',p%iprcparm(p_type_),p%iprcparm(n_ovr_) if(debug) write(0,*)me,': calling psb_asmatbld',p%iprcparm(p_type_),p%iprcparm(n_ovr_)
if (debug) call psb_barrier(ictxt) if (debug) call psb_barrier(ictxt)
@ -155,7 +154,7 @@ subroutine psb_zilu_bld(a,desc_a,p,upd,info)
call psb_errpush(info,name,a_err=ch_err) call psb_errpush(info,name,a_err=ch_err)
goto 9999 goto 9999
end if end if
t2= mpi_wtime() t2= psb_wtime()
if (debug) write(0,*)me,': out of psb_asmatbld' if (debug) write(0,*)me,': out of psb_asmatbld'
if (debug) call psb_barrier(ictxt) if (debug) call psb_barrier(ictxt)
@ -240,7 +239,7 @@ subroutine psb_zilu_bld(a,desc_a,p,upd,info)
goto 9999 goto 9999
end if end if
t3 = mpi_wtime() t3 = psb_wtime()
if (debugprt) then if (debugprt) then
call psb_barrier(ictxt) call psb_barrier(ictxt)
open(40+me) open(40+me)
@ -253,7 +252,7 @@ subroutine psb_zilu_bld(a,desc_a,p,upd,info)
! !
! Ok, factor the matrix. ! Ok, factor the matrix.
! !
t5 = mpi_wtime() t5 = psb_wtime()
blck%m=0 blck%m=0
call psb_ilu_fct(atmp,p%av(l_pr_),p%av(u_pr_),p%d,info,blck=blck) call psb_ilu_fct(atmp,p%av(l_pr_),p%av(u_pr_),p%d,info,blck=blck)
if(info/=0) then if(info/=0) then
@ -273,7 +272,7 @@ subroutine psb_zilu_bld(a,desc_a,p,upd,info)
else if (p%iprcparm(iren_) == 0) then else if (p%iprcparm(iren_) == 0) then
t3 = mpi_wtime() t3 = psb_wtime()
! This is where we have mo renumbering, thus no need ! This is where we have mo renumbering, thus no need
! for ATMP ! for ATMP
@ -289,7 +288,7 @@ subroutine psb_zilu_bld(a,desc_a,p,upd,info)
close(40+me) close(40+me)
endif endif
t5= mpi_wtime() t5= psb_wtime()
if (debug) write(0,*) me,' Going for ilu_fct' if (debug) write(0,*) me,' Going for ilu_fct'
if (debug) call psb_barrier(ictxt) if (debug) call psb_barrier(ictxt)
call psb_ilu_fct(a,p%av(l_pr_),p%av(u_pr_),p%d,info,blck=blck) call psb_ilu_fct(a,p%av(l_pr_),p%av(u_pr_),p%d,info,blck=blck)
@ -321,7 +320,7 @@ subroutine psb_zilu_bld(a,desc_a,p,upd,info)
! ierr = MPE_Log_event( ifcte, 0, "st SIMPLE" ) ! ierr = MPE_Log_event( ifcte, 0, "st SIMPLE" )
t6 = mpi_wtime() t6 = psb_wtime()
! !
! write(0,'(i3,1x,a,3(1x,g18.9))') me,'renum/factor time',t3-t2,t6-t5 ! write(0,'(i3,1x,a,3(1x,g18.9))') me,'renum/factor time',t3-t2,t6-t5
! if (me==0) write(0,'(a,3(1x,g18.9))') 'renum/factor time',t3-t2,t6-t5 ! if (me==0) write(0,'(a,3(1x,g18.9))') 'renum/factor time',t3-t2,t6-t5

@ -101,10 +101,9 @@ subroutine psb_zmlprc_aply(alpha,baseprecv,x,beta,y,desc_data,trans,work,info)
character ::diagl, diagu character ::diagl, diagu
integer :: ictxt,np,me,i, isz, nrg,nr2l,err_act, iptype, int_err(5) integer :: ictxt,np,me,i, isz, nrg,nr2l,err_act, iptype, int_err(5)
real(kind(1.d0)) :: omega real(kind(1.d0)) :: omega
real(kind(1.d0)) :: t1, t2, t3, t4, t5, t6, t7, mpi_wtime real(kind(1.d0)) :: t1, t2, t3, t4, t5, t6, t7
logical, parameter :: debug=.false., debugprt=.false. logical, parameter :: debug=.false., debugprt=.false.
integer :: ismth, nlev, ilev integer :: ismth, nlev, ilev
external mpi_wtime
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
type psb_mlprec_wrk_type type psb_mlprec_wrk_type

@ -52,7 +52,6 @@ subroutine psb_zprc_aply(prec,x,y,desc_data,info,trans, work)
complex(kind(1.d0)), pointer :: work_(:) complex(kind(1.d0)), pointer :: work_(:)
integer :: ictxt,np,me,err_act integer :: ictxt,np,me,err_act
logical,parameter :: debug=.false., debugprt=.false. logical,parameter :: debug=.false., debugprt=.false.
external mpi_wtime
character(len=20) :: name character(len=20) :: name
interface psb_baseprc_aply interface psb_baseprc_aply

@ -53,8 +53,7 @@ subroutine psb_zsp_renum(a,desc_a,blck,p,atmp,info)
integer ::ictxt,np,me, err_act integer ::ictxt,np,me, err_act
integer, allocatable :: itmp(:), itmp2(:) integer, allocatable :: itmp(:), itmp2(:)
complex(kind(1.d0)), allocatable :: ztmp(:) complex(kind(1.d0)), allocatable :: ztmp(:)
real(kind(1.d0)) :: t1,t2,t3,t4,t5,t6,mpi_wtime, t7, t8 real(kind(1.d0)) :: t1,t2,t3,t4,t5,t6, t7, t8
external mpi_wtime
if (psb_get_errstatus().ne.0) return if (psb_get_errstatus().ne.0) return
info=0 info=0
@ -101,7 +100,7 @@ subroutine psb_zsp_renum(a,desc_a,blck,p,atmp,info)
do k=1, nnr do k=1, nnr
p%invperm(p%perm(k)) = k p%invperm(p%perm(k)) = k
enddo enddo
t3 = mpi_wtime() t3 = psb_wtime()
! Build ATMP with new numbering. ! Build ATMP with new numbering.
nztmp=size(atmp%aspk) nztmp=size(atmp%aspk)
@ -178,7 +177,7 @@ subroutine psb_zsp_renum(a,desc_a,blck,p,atmp,info)
enddo enddo
t4 = mpi_wtime() t4 = psb_wtime()
deallocate(itmp,itmp2,ztmp) deallocate(itmp,itmp2,ztmp)
@ -262,7 +261,7 @@ subroutine psb_zsp_renum(a,desc_a,blck,p,atmp,info)
do k=1, nnr do k=1, nnr
p%invperm(p%perm(k)) = k p%invperm(p%perm(k)) = k
enddo enddo
t3 = mpi_wtime() t3 = psb_wtime()
! Build ATMP with new numbering. ! Build ATMP with new numbering.
@ -339,7 +338,7 @@ subroutine psb_zsp_renum(a,desc_a,blck,p,atmp,info)
enddo enddo
t4 = mpi_wtime() t4 = psb_wtime()

Loading…
Cancel
Save