mld2p4-2:

Reference version with latest fixes on minenergy, before complete
restructuring the preconditioner data types.
stopcriterion
Salvatore Filippone 15 years ago
parent 07c209137b
commit 253fed9591

@ -591,14 +591,15 @@ subroutine mld_daggrmat_minnrg_asb(a,desc_a,ilaggr,nlaggr,p,info)
!!$ call psb_spcnv(atmp,atmp2,info,afmt='coo') !!$ call psb_spcnv(atmp,atmp2,info,afmt='coo')
!!$ if (info == 0) call psb_spcnv(atmp2,info,afmt='csc') !!$ if (info == 0) call psb_spcnv(atmp2,info,afmt='csc')
!!$ !!$
!!$ do i=1, ncol !!$ do i=1, nrow
!!$ omf(i) = ommx !!$ omf(i) = ommx
!!$ do j=atmp2%ia2(i),atmp2%ia2(i+1)-1 !!$ do j=atmp2%ia2(i),atmp2%ia2(i+1)-1
!!$ omf(i) = min(omf(i),omi(atmp2%ia1(j))) !!$ omf(i) = min(omf(i),omi(atmp2%ia1(j)))
!!$ end do !!$ end do
!!$ omf(i) = max(dzero,omf(i)) !!$ omf(i) = max(dzero,omf(i))
!!$ end do !!$ end do
!!$ omf(1:ncol) = omf(1:ncol)*adinv(1:ncol) !!$ omf(1:nrow) = omf(1:nrow)*adinv(1:nrow)
!!$ call psb_halo(omf,desc_a,info)
!!$ call psb_sp_free(atmp2,info) !!$ call psb_sp_free(atmp2,info)
!!$ !!$
!!$ !!$

@ -75,7 +75,7 @@ module mld_prec_type
& psb_sizeof_int, psb_sizeof_long_int, psb_sizeof_sp, psb_sizeof_dp, psb_sizeof,& & psb_sizeof_int, psb_sizeof_long_int, psb_sizeof_sp, psb_sizeof_dp, psb_sizeof,&
& psb_cd_get_context, psb_info & psb_cd_get_context, psb_info
use psb_prec_mod, only: psb_sprec_type, psb_dprec_type,& use psb_prec_mod, only: psb_sprec_type, psb_dprec_type,&
& psb_cprec_type, psb_zprec_type & psb_cprec_type, psb_zprec_type, psb_d_base_prec_type
! !
! Type: mld_Tprec_type. ! Type: mld_Tprec_type.
@ -219,7 +219,7 @@ module mld_prec_type
procedure, pass(prec) :: s_apply1v => mld_s_apply1v procedure, pass(prec) :: s_apply1v => mld_s_apply1v
end type mld_sprec_type end type mld_sprec_type
type mld_dbaseprec_type type, extends(psb_d_base_prec_type) :: mld_dbaseprec_type
type(psb_d_sparse_mat), allocatable :: av(:) type(psb_d_sparse_mat), allocatable :: av(:)
real(psb_dpk_), allocatable :: d(:) real(psb_dpk_), allocatable :: d(:)
type(psb_desc_type) :: desc_data type(psb_desc_type) :: desc_data
@ -229,6 +229,7 @@ module mld_prec_type
end type mld_dbaseprec_type end type mld_dbaseprec_type
type mld_donelev_type type mld_donelev_type
class(psb_d_base_prec_type), allocatable :: bprec
type(mld_dbaseprec_type) :: prec type(mld_dbaseprec_type) :: prec
integer, allocatable :: iprcparm(:) integer, allocatable :: iprcparm(:)
real(psb_dpk_), allocatable :: rprcparm(:) real(psb_dpk_), allocatable :: rprcparm(:)

@ -15,7 +15,7 @@ ILU ! Subdomain solver ILU MILU ILUT UMF SLU
1 ! Level-set N for ILU(N) 1 ! Level-set N for ILU(N)
1.d-4 ! Threshold T for ILU(T,P) 1.d-4 ! Threshold T for ILU(T,P)
3 ! Number of levels in a multilevel preconditioner 3 ! Number of levels in a multilevel preconditioner
NONSMOOTHED ! Kind of aggregation: SMOOTHED, NONSMOOTHED, MINENERGY SMOOTHED ! Kind of aggregation: SMOOTHED, NONSMOOTHED, MINENERGY
DEC ! Type of aggregation DEC SYMDEC GLB DEC ! Type of aggregation DEC SYMDEC GLB
MULT ! Type of multilevel correction: ADD MULT MULT ! Type of multilevel correction: ADD MULT
TWOSIDE ! Side of mult. correction PRE POST TWOSIDE (ignored for ADD) TWOSIDE ! Side of mult. correction PRE POST TWOSIDE (ignored for ADD)

@ -86,7 +86,7 @@ program spde
real(psb_dpk_) :: t1, t2, tprec real(psb_dpk_) :: t1, t2, tprec
! sparse matrix and preconditioner ! sparse matrix and preconditioner
type(psb_sspmat_type) :: a type(psb_s_sparse_mat) :: a
type(mld_sprec_type) :: prec type(mld_sprec_type) :: prec
! descriptor ! descriptor
type(psb_desc_type) :: desc_a type(psb_desc_type) :: desc_a
@ -145,7 +145,7 @@ program spde
! !
! get parameters ! get parameters
! !
call get_parms(ictxt,kmethd,prectype,afmt,idim,istopc,itmax,itrace,irst) call get_parms(ictxt,kmethd,prectype,afmt,idim,istopc,itmax,itrace,irst,eps)
! !
! allocate and fill in the coefficient matrix, rhs and initial guess ! allocate and fill in the coefficient matrix, rhs and initial guess
@ -219,7 +219,6 @@ program spde
if(iam == psb_root_) write(*,'("Calling iterative method ",a)')kmethd if(iam == psb_root_) write(*,'("Calling iterative method ",a)')kmethd
call psb_barrier(ictxt) call psb_barrier(ictxt)
t1 = psb_wtime() t1 = psb_wtime()
eps = 1.d-9
call psb_krylov(kmethd,a,prec,b,x,eps,desc_a,info,& call psb_krylov(kmethd,a,prec,b,x,eps,desc_a,info,&
& itmax=itmax,iter=iter,err=err,itrace=itrace,istop=istopc,irst=irst) & itmax=itmax,iter=iter,err=err,itrace=itrace,istop=istopc,irst=irst)
@ -278,12 +277,13 @@ contains
! !
! get iteration parameters from standard input ! get iteration parameters from standard input
! !
subroutine get_parms(ictxt,kmethd,prectype,afmt,idim,istopc,itmax,itrace,irst) subroutine get_parms(ictxt,kmethd,prectype,afmt,idim,istopc,itmax,itrace,irst,eps)
integer :: ictxt integer :: ictxt
type(precdata) :: prectype type(precdata) :: prectype
character(len=*) :: kmethd, afmt character(len=*) :: kmethd, afmt
integer :: idim, istopc,itmax,itrace,irst integer :: idim, istopc,itmax,itrace,irst
integer :: np, iam, info integer :: np, iam, info
real(psb_spk_) :: eps
character(len=20) :: buffer character(len=20) :: buffer
call psb_info(ictxt, iam, np) call psb_info(ictxt, iam, np)
@ -329,6 +329,7 @@ contains
call psb_bcast(ictxt,itmax) call psb_bcast(ictxt,itmax)
call psb_bcast(ictxt,itrace) call psb_bcast(ictxt,itrace)
call psb_bcast(ictxt,irst) call psb_bcast(ictxt,irst)
call psb_bcast(ictxt,eps)
call psb_bcast(ictxt,prectype%descr) ! verbose description of the prec call psb_bcast(ictxt,prectype%descr) ! verbose description of the prec
@ -417,7 +418,7 @@ contains
type(psb_desc_type) :: desc_a type(psb_desc_type) :: desc_a
integer :: ictxt, info integer :: ictxt, info
character :: afmt*5 character :: afmt*5
type(psb_sspmat_type) :: a type(psb_s_sparse_mat) :: a
real(psb_spk_) :: zt(nb),glob_x,glob_y,glob_z real(psb_spk_) :: zt(nb),glob_x,glob_y,glob_z
integer :: m,n,nnz,glob_row,nlr,i,ii,ib,k integer :: m,n,nnz,glob_row,nlr,i,ii,ib,k
integer :: x,y,z,ia,indx_owner integer :: x,y,z,ia,indx_owner
@ -679,8 +680,9 @@ contains
call psb_amx(ictxt,tasb) call psb_amx(ictxt,tasb)
call psb_amx(ictxt,ttot) call psb_amx(ictxt,ttot)
if(iam == psb_root_) then if(iam == psb_root_) then
ch_err = a%get_fmt()
write(*,'("The matrix has been generated and assembled in ",a3," format.")')& write(*,'("The matrix has been generated and assembled in ",a3," format.")')&
& a%fida(1:3) & ch_err(1:3)
write(*,'("-allocation time : ",es12.5)') talc write(*,'("-allocation time : ",es12.5)') talc
write(*,'("-coeff. gen. time : ",es12.5)') tgen write(*,'("-coeff. gen. time : ",es12.5)') tgen
write(*,'("-assembly time : ",es12.5)') tasb write(*,'("-assembly time : ",es12.5)') tasb

Loading…
Cancel
Save