mlprec/mld_caggr_bld.f90
 mlprec/mld_caggrmap_bld.f90
 mlprec/mld_cprecbld.f90
 mlprec/mld_daggr_bld.f90
 mlprec/mld_daggrmap_bld.f90
 mlprec/mld_dprecbld.f90
 mlprec/mld_inner_mod.f90
 mlprec/mld_prec_type.f90
 mlprec/mld_saggr_bld.f90
 mlprec/mld_saggrmap_bld.f90
 mlprec/mld_sprecbld.f90
 mlprec/mld_zaggr_bld.f90
 mlprec/mld_zaggrmap_bld.f90
 mlprec/mld_zprecbld.f90

Switched name from aggr_bld to coarse_bld, step 1.
stopcriterion
Salvatore Filippone 16 years ago
parent a8e13e2c18
commit c3f34ba307

@ -36,9 +36,9 @@
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
! File: mld_caggr_bld.f90
! File: mld_ccoarse_bld.f90
!
! Subroutine: mld_caggr_bld
! Subroutine: mld_ccoarse_bld
! Version: complex
!
! This routine builds the preconditioner corresponding to the current
@ -60,10 +60,10 @@
! info - integer, output.
! Error code.
!
subroutine mld_caggr_bld(a,desc_a,p,info)
subroutine mld_ccoarse_bld(a,desc_a,p,info)
use psb_base_mod
use mld_inner_mod, mld_protect_name => mld_caggr_bld
use mld_inner_mod, mld_protect_name => mld_ccoarse_bld
implicit none
@ -80,7 +80,7 @@ subroutine mld_caggr_bld(a,desc_a,p,info)
integer :: ictxt, np, me, err_act
integer, allocatable :: ilaggr(:), nlaggr(:)
name='mld_caggr_bld'
name='mld_ccoarse_bld'
if (psb_get_errstatus().ne.0) return
call psb_erractionsave(err_act)
info = 0
@ -117,7 +117,7 @@ subroutine mld_caggr_bld(a,desc_a,p,info)
! the coarse to the fine level.
!
call mld_aggrmap_bld(p%iprcparm(mld_aggr_alg_),p%rprcparm(mld_aggr_thresh_),&
& a,desc_a,nlaggr,ilaggr,info)
& a,desc_a,ilaggr,nlaggr,info)
if(info /= 0) then
call psb_errpush(4010,name,a_err='mld_aggrmap_bld')
goto 9999
@ -151,4 +151,4 @@ subroutine mld_caggr_bld(a,desc_a,p,info)
end if
Return
end subroutine mld_caggr_bld
end subroutine mld_ccoarse_bld

@ -79,7 +79,7 @@
! info - integer, output.
! Error code.
!
subroutine mld_caggrmap_bld(aggr_type,theta,a,desc_a,nlaggr,ilaggr,info)
subroutine mld_caggrmap_bld(aggr_type,theta,a,desc_a,ilaggr,nlaggr,info)
use psb_base_mod
use mld_inner_mod, mld_protect_name => mld_caggrmap_bld

@ -212,7 +212,7 @@ subroutine mld_cprecbld(a,desc_a,p,info)
! Build the mapping between levels (i-1) and (i)
!
call init_baseprec_av(p%precv(i)%prec,info)
if (info == 0) call mld_aggr_bld(p%precv(i-1)%base_a,&
if (info == 0) call mld_coarse_bld(p%precv(i-1)%base_a,&
& p%precv(i-1)%base_desc, p%precv(i),info)
if (info /= 0) then
@ -276,7 +276,7 @@ subroutine mld_cprecbld(a,desc_a,p,info)
i = iszv
call check_coarse_lev(p%precv(i))
call init_baseprec_av(p%precv(i)%prec,info)
if (info == 0) call mld_aggr_bld(p%precv(i-1)%base_a,&
if (info == 0) call mld_coarse_bld(p%precv(i-1)%base_a,&
& p%precv(i-1)%base_desc, p%precv(i),info)
if (info /= 0) then
call psb_errpush(4010,name,a_err='coarse rebuild')

@ -36,9 +36,9 @@
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
! File: mld_daggr_bld.f90
! File: mld_dcoarse_bld.f90
!
! Subroutine: mld_daggr_bld
! Subroutine: mld_dcoarse_bld
! Version: real
!
! This routine builds the preconditioner corresponding to the current
@ -60,10 +60,10 @@
! info - integer, output.
! Error code.
!
subroutine mld_daggr_bld(a,desc_a,p,info)
subroutine mld_dcoarse_bld(a,desc_a,p,info)
use psb_base_mod
use mld_inner_mod, mld_protect_name => mld_daggr_bld
use mld_inner_mod, mld_protect_name => mld_dcoarse_bld
implicit none
@ -80,7 +80,7 @@ subroutine mld_daggr_bld(a,desc_a,p,info)
integer :: ictxt, np, me, err_act
integer, allocatable :: ilaggr(:), nlaggr(:)
name='mld_daggr_bld'
name='mld_dcoarse_bld'
if (psb_get_errstatus().ne.0) return
call psb_erractionsave(err_act)
info = 0
@ -117,7 +117,7 @@ subroutine mld_daggr_bld(a,desc_a,p,info)
! the coarse to the fine level.
!
call mld_aggrmap_bld(p%iprcparm(mld_aggr_alg_),p%rprcparm(mld_aggr_thresh_),&
& a,desc_a,nlaggr,ilaggr,info)
& a,desc_a,ilaggr,nlaggr,info)
if(info /= 0) then
call psb_errpush(4010,name,a_err='mld_aggrmap_bld')
goto 9999
@ -151,4 +151,4 @@ subroutine mld_daggr_bld(a,desc_a,p,info)
end if
Return
end subroutine mld_daggr_bld
end subroutine mld_dcoarse_bld

@ -79,7 +79,7 @@
! info - integer, output.
! Error code.
!
subroutine mld_daggrmap_bld(aggr_type,theta,a,desc_a,nlaggr,ilaggr,info)
subroutine mld_daggrmap_bld(aggr_type,theta,a,desc_a,ilaggr,nlaggr,info)
use psb_base_mod
use mld_inner_mod, mld_protect_name => mld_daggrmap_bld

@ -212,7 +212,7 @@ subroutine mld_dprecbld(a,desc_a,p,info)
! Build the mapping between levels (i-1) and (i)
!
call init_baseprec_av(p%precv(i)%prec,info)
if (info == 0) call mld_aggr_bld(p%precv(i-1)%base_a,&
if (info == 0) call mld_coarse_bld(p%precv(i-1)%base_a,&
& p%precv(i-1)%base_desc, p%precv(i),info)
if (info /= 0) then
@ -276,7 +276,7 @@ subroutine mld_dprecbld(a,desc_a,p,info)
i = iszv
call check_coarse_lev(p%precv(i))
call init_baseprec_av(p%precv(i)%prec,info)
if (info == 0) call mld_aggr_bld(p%precv(i-1)%base_a,&
if (info == 0) call mld_coarse_bld(p%precv(i-1)%base_a,&
& p%precv(i-1)%base_desc, p%precv(i),info)
if (info /= 0) then
call psb_errpush(4010,name,a_err='coarse rebuild')

@ -384,43 +384,43 @@ module mld_inner_mod
end subroutine mld_zsp_renum
end interface
interface mld_aggr_bld
subroutine mld_saggr_bld(a,desc_a,p,info)
interface mld_coarse_bld
subroutine mld_scoarse_bld(a,desc_a,p,info)
use psb_base_mod, only : psb_sspmat_type, psb_desc_type, psb_spk_
use mld_prec_type, only : mld_sbaseprec_type, mld_s_onelev_type
type(psb_sspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(mld_s_onelev_type), intent(inout), target :: p
integer, intent(out) :: info
end subroutine mld_saggr_bld
subroutine mld_daggr_bld(a,desc_a,p,info)
end subroutine mld_scoarse_bld
subroutine mld_dcoarse_bld(a,desc_a,p,info)
use psb_base_mod, only : psb_dspmat_type, psb_desc_type, psb_dpk_
use mld_prec_type, only : mld_dbaseprec_type, mld_d_onelev_type
type(psb_dspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(mld_d_onelev_type), intent(inout), target :: p
integer, intent(out) :: info
end subroutine mld_daggr_bld
subroutine mld_caggr_bld(a,desc_a,p,info)
end subroutine mld_dcoarse_bld
subroutine mld_ccoarse_bld(a,desc_a,p,info)
use psb_base_mod, only : psb_cspmat_type, psb_desc_type, psb_spk_
use mld_prec_type, only : mld_cbaseprec_type, mld_c_onelev_type
type(psb_cspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(mld_c_onelev_type), intent(inout), target :: p
integer, intent(out) :: info
end subroutine mld_caggr_bld
subroutine mld_zaggr_bld(a,desc_a,p,info)
end subroutine mld_ccoarse_bld
subroutine mld_zcoarse_bld(a,desc_a,p,info)
use psb_base_mod, only : psb_zspmat_type, psb_desc_type, psb_dpk_
use mld_prec_type, only : mld_zbaseprec_type, mld_z_onelev_type
type(psb_zspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(mld_z_onelev_type), intent(inout), target :: p
integer, intent(out) :: info
end subroutine mld_zaggr_bld
end subroutine mld_zcoarse_bld
end interface
interface mld_aggrmap_bld
subroutine mld_saggrmap_bld(aggr_type,theta,a,desc_a,nlaggr,ilaggr,info)
subroutine mld_saggrmap_bld(aggr_type,theta,a,desc_a,ilaggr,nlaggr,info)
use psb_base_mod, only : psb_sspmat_type, psb_desc_type, psb_spk_
use mld_prec_type, only : mld_sbaseprec_type
integer, intent(in) :: aggr_type
@ -430,7 +430,7 @@ module mld_inner_mod
integer, allocatable, intent(out) :: ilaggr(:),nlaggr(:)
integer, intent(out) :: info
end subroutine mld_saggrmap_bld
subroutine mld_daggrmap_bld(aggr_type,theta,a,desc_a,nlaggr,ilaggr,info)
subroutine mld_daggrmap_bld(aggr_type,theta,a,desc_a,ilaggr,nlaggr,info)
use psb_base_mod, only : psb_dspmat_type, psb_desc_type, psb_dpk_
use mld_prec_type, only : mld_dbaseprec_type
integer, intent(in) :: aggr_type
@ -440,7 +440,7 @@ module mld_inner_mod
integer, allocatable, intent(out) :: ilaggr(:),nlaggr(:)
integer, intent(out) :: info
end subroutine mld_daggrmap_bld
subroutine mld_caggrmap_bld(aggr_type,theta,a,desc_a,nlaggr,ilaggr,info)
subroutine mld_caggrmap_bld(aggr_type,theta,a,desc_a,ilaggr,nlaggr,info)
use psb_base_mod, only : psb_cspmat_type, psb_desc_type, psb_spk_
use mld_prec_type, only : mld_cbaseprec_type
integer, intent(in) :: aggr_type
@ -450,7 +450,7 @@ module mld_inner_mod
integer, allocatable, intent(out) :: ilaggr(:),nlaggr(:)
integer, intent(out) :: info
end subroutine mld_caggrmap_bld
subroutine mld_zaggrmap_bld(aggr_type,theta,a,desc_a,nlaggr,ilaggr,info)
subroutine mld_zaggrmap_bld(aggr_type,theta,a,desc_a,ilaggr,nlaggr,info)
use psb_base_mod, only : psb_zspmat_type, psb_desc_type, psb_dpk_
use mld_prec_type, only : mld_zbaseprec_type
integer, intent(in) :: aggr_type

@ -1916,8 +1916,6 @@ contains
type(mld_sbaseprec_type), intent(inout) :: p
nullify(p%base_a)
nullify(p%base_desc)
end subroutine mld_nullify_sbaseprec
@ -2022,8 +2020,6 @@ contains
type(mld_dbaseprec_type), intent(inout) :: p
nullify(p%base_a)
nullify(p%base_desc)
end subroutine mld_nullify_dbaseprec
@ -2136,8 +2132,6 @@ contains
type(mld_cbaseprec_type), intent(inout) :: p
nullify(p%base_a)
nullify(p%base_desc)
end subroutine mld_nullify_cbaseprec
@ -2245,8 +2239,6 @@ contains
type(mld_zbaseprec_type), intent(inout) :: p
nullify(p%base_a)
nullify(p%base_desc)
end subroutine mld_nullify_zbaseprec

@ -36,9 +36,9 @@
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
! File: mld_saggr_bld.f90
! File: mld_scoarse_bld.f90
!
! Subroutine: mld_saggr_bld
! Subroutine: mld_scoarse_bld
! Version: real
!
! This routine builds the preconditioner corresponding to the current
@ -60,10 +60,10 @@
! info - integer, output.
! Error code.
!
subroutine mld_saggr_bld(a,desc_a,p,info)
subroutine mld_scoarse_bld(a,desc_a,p,info)
use psb_base_mod
use mld_inner_mod, mld_protect_name => mld_saggr_bld
use mld_inner_mod, mld_protect_name => mld_scoarse_bld
implicit none
@ -80,7 +80,7 @@ subroutine mld_saggr_bld(a,desc_a,p,info)
integer :: ictxt, np, me, err_act
integer, allocatable :: ilaggr(:), nlaggr(:)
name='mld_saggr_bld'
name='mld_scoarse_bld'
if (psb_get_errstatus().ne.0) return
call psb_erractionsave(err_act)
info = 0
@ -117,7 +117,7 @@ subroutine mld_saggr_bld(a,desc_a,p,info)
! the coarse to the fine level.
!
call mld_aggrmap_bld(p%iprcparm(mld_aggr_alg_),p%rprcparm(mld_aggr_thresh_),&
& a,desc_a,nlaggr,ilaggr,info)
& a,desc_a,ilaggr,nlaggr,info)
if(info /= 0) then
call psb_errpush(4010,name,a_err='mld_aggrmap_bld')
goto 9999
@ -151,4 +151,4 @@ subroutine mld_saggr_bld(a,desc_a,p,info)
end if
Return
end subroutine mld_saggr_bld
end subroutine mld_scoarse_bld

@ -79,7 +79,7 @@
! info - integer, output.
! Error code.
!
subroutine mld_saggrmap_bld(aggr_type,theta,a,desc_a,nlaggr,ilaggr,info)
subroutine mld_saggrmap_bld(aggr_type,theta,a,desc_a,ilaggr,nlaggr,info)
use psb_base_mod
use mld_inner_mod, mld_protect_name => mld_saggrmap_bld

@ -212,7 +212,7 @@ subroutine mld_sprecbld(a,desc_a,p,info)
! Build the mapping between levels (i-1) and (i)
!
call init_baseprec_av(p%precv(i)%prec,info)
if (info == 0) call mld_aggr_bld(p%precv(i-1)%base_a,&
if (info == 0) call mld_coarse_bld(p%precv(i-1)%base_a,&
& p%precv(i-1)%base_desc, p%precv(i),info)
if (info /= 0) then
@ -276,7 +276,7 @@ subroutine mld_sprecbld(a,desc_a,p,info)
i = iszv
call check_coarse_lev(p%precv(i))
call init_baseprec_av(p%precv(i)%prec,info)
if (info == 0) call mld_aggr_bld(p%precv(i-1)%base_a,&
if (info == 0) call mld_coarse_bld(p%precv(i-1)%base_a,&
& p%precv(i-1)%base_desc, p%precv(i),info)
if (info /= 0) then
call psb_errpush(4010,name,a_err='coarse rebuild')

@ -36,9 +36,9 @@
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
! File: mld_zaggr_bld.f90
! File: mld_zcoarse_bld.f90
!
! Subroutine: mld_zaggr_bld
! Subroutine: mld_zcoarse_bld
! Version: complex
!
! This routine builds the preconditioner corresponding to the current
@ -60,10 +60,10 @@
! info - integer, output.
! Error code.
!
subroutine mld_zaggr_bld(a,desc_a,p,info)
subroutine mld_zcoarse_bld(a,desc_a,p,info)
use psb_base_mod
use mld_inner_mod, mld_protect_name => mld_zaggr_bld
use mld_inner_mod, mld_protect_name => mld_zcoarse_bld
implicit none
@ -80,7 +80,7 @@ subroutine mld_zaggr_bld(a,desc_a,p,info)
integer :: ictxt, np, me, err_act
integer, allocatable :: ilaggr(:), nlaggr(:)
name='mld_zaggr_bld'
name='mld_zcoarse_bld'
if (psb_get_errstatus().ne.0) return
call psb_erractionsave(err_act)
info = 0
@ -117,7 +117,7 @@ subroutine mld_zaggr_bld(a,desc_a,p,info)
! the coarse to the fine level.
!
call mld_aggrmap_bld(p%iprcparm(mld_aggr_alg_),p%rprcparm(mld_aggr_thresh_),&
& a,desc_a,nlaggr,ilaggr,info)
& a,desc_a,ilaggr,nlaggr,info)
if(info /= 0) then
call psb_errpush(4010,name,a_err='mld_aggrmap_bld')
goto 9999
@ -151,4 +151,4 @@ subroutine mld_zaggr_bld(a,desc_a,p,info)
end if
Return
end subroutine mld_zaggr_bld
end subroutine mld_zcoarse_bld

@ -79,7 +79,7 @@
! info - integer, output.
! Error code.
!
subroutine mld_zaggrmap_bld(aggr_type,theta,a,desc_a,nlaggr,ilaggr,info)
subroutine mld_zaggrmap_bld(aggr_type,theta,a,desc_a,ilaggr,nlaggr,info)
use psb_base_mod
use mld_inner_mod, mld_protect_name => mld_zaggrmap_bld

@ -212,7 +212,7 @@ subroutine mld_zprecbld(a,desc_a,p,info)
! Build the mapping between levels (i-1) and (i)
!
call init_baseprec_av(p%precv(i)%prec,info)
if (info == 0) call mld_aggr_bld(p%precv(i-1)%base_a,&
if (info == 0) call mld_coarse_bld(p%precv(i-1)%base_a,&
& p%precv(i-1)%base_desc, p%precv(i),info)
if (info /= 0) then
@ -276,7 +276,7 @@ subroutine mld_zprecbld(a,desc_a,p,info)
i = iszv
call check_coarse_lev(p%precv(i))
call init_baseprec_av(p%precv(i)%prec,info)
if (info == 0) call mld_aggr_bld(p%precv(i-1)%base_a,&
if (info == 0) call mld_coarse_bld(p%precv(i-1)%base_a,&
& p%precv(i-1)%base_desc, p%precv(i),info)
if (info /= 0) then
call psb_errpush(4010,name,a_err='coarse rebuild')

Loading…
Cancel
Save