Fixed INTENT(OUT) on AC,DESC_AC on AGGRMAT_ASB.

Changed subroutine name is_legal_ml_aggr_kind into is_legal_ml_aggr_alg.
stopcriterion
Salvatore Filippone 17 years ago
parent 55d8db4c62
commit 76eaf13fcf

@ -99,15 +99,15 @@ subroutine mld_daggrmat_asb(a,desc_a,ac,desc_ac,p,info)
implicit none
! Arguments
type(psb_dspmat_type), intent(in), target :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dspmat_type), intent(inout), target :: ac
type(psb_desc_type), intent(inout) :: desc_ac
type(psb_dspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dspmat_type), intent(out) :: ac
type(psb_desc_type), intent(out) :: desc_ac
type(mld_dbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
integer, intent(out) :: info
! Local variables
integer ::ictxt,np,me, err_act, icomm
integer :: ictxt,np,me, err_act, icomm
character(len=20) :: name
name='mld_aggrmat_asb'

@ -87,10 +87,10 @@ subroutine mld_daggrmat_raw_asb(a,desc_a,ac,desc_ac,p,info)
#endif
! Arguments
type(psb_dspmat_type), intent(in), target :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dspmat_type), intent(inout), target :: ac
type(psb_desc_type), intent(inout) :: desc_ac
type(psb_dspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dspmat_type), intent(out) :: ac
type(psb_desc_type), intent(out) :: desc_ac
type(mld_dbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info

@ -105,12 +105,12 @@ subroutine mld_daggrmat_smth_asb(a,desc_a,ac,desc_ac,p,info)
#endif
! Arguments
type(psb_dspmat_type), intent(in), target :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dspmat_type), intent(inout), target :: ac
type(psb_desc_type), intent(inout) :: desc_ac
type(mld_dbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
type(psb_dspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dspmat_type), intent(out) :: ac
type(psb_desc_type), intent(out) :: desc_ac
type(mld_dbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
! Local variables
type(psb_dspmat_type) :: b
@ -244,7 +244,7 @@ subroutine mld_daggrmat_smth_asb(a,desc_a,ac,desc_ac,p,info)
call psb_spcnv(am4,info,afmt='csr',dupl=psb_dupl_add_)
if (info==0) call psb_spcnv(a,am3,info,afmt='csr')
if (info==0) call psb_spcnv(a,am3,info,afmt='csr',dupl=psb_dupl_add_)
if (info /= 0) then
call psb_errpush(4010,name,a_err='spcnv')
goto 9999

@ -90,7 +90,7 @@ subroutine mld_dmlprec_bld(a,desc_a,p,info)
call mld_check_def(p%iprcparm(mld_ml_type_),'Multilevel type',&
& mld_mult_ml_,is_legal_ml_type)
call mld_check_def(p%iprcparm(mld_aggr_alg_),'Aggregation',&
& mld_dec_aggr_,is_legal_ml_aggr_kind)
& mld_dec_aggr_,is_legal_ml_aggr_alg)
call mld_check_def(p%iprcparm(mld_aggr_kind_),'Smoother',&
& mld_smooth_prol_,is_legal_ml_smth_kind)
call mld_check_def(p%iprcparm(mld_coarse_mat_),'Coarse matrix',&
@ -127,8 +127,6 @@ subroutine mld_dmlprec_bld(a,desc_a,p,info)
! the mapping defined by mld_aggrmap_bld and applying the aggregation
! algorithm specified by p%iprcparm(mld_aggr_kind_)
!
call psb_nullify_sp(ac)
call psb_nullify_desc(desc_ac)
call mld_aggrmat_asb(a,desc_a,ac,desc_ac,p,info)
if(info /= 0) then
call psb_errpush(4010,name,a_err='mld_aggrmat_asb')

@ -628,22 +628,22 @@ module mld_prec_mod
subroutine mld_daggrmat_asb(a,desc_a,ac,desc_ac,p,info)
use psb_base_mod
use mld_prec_type
type(psb_dspmat_type), intent(in), target :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dspmat_type), intent(inout),target :: ac
type(psb_desc_type), intent(inout) :: desc_ac
type(psb_dspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dspmat_type), intent(out) :: ac
type(psb_desc_type), intent(out) :: desc_ac
type(mld_dbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
integer, intent(out) :: info
end subroutine mld_daggrmat_asb
subroutine mld_zaggrmat_asb(a,desc_a,ac,desc_ac,p,info)
use psb_base_mod
use mld_prec_type
type(psb_zspmat_type), intent(in), target :: a
type(mld_zbaseprc_type), intent(inout),target :: p
type(psb_zspmat_type), intent(inout),target :: ac
type(psb_desc_type), intent(in) :: desc_a
type(psb_desc_type), intent(inout) :: desc_ac
integer, intent(out) :: info
type(psb_zspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_zspmat_type), intent(out) :: ac
type(psb_desc_type), intent(out) :: desc_ac
type(mld_zbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
end subroutine mld_zaggrmat_asb
end interface
@ -651,22 +651,22 @@ module mld_prec_mod
subroutine mld_daggrmat_raw_asb(a,desc_a,ac,desc_ac,p,info)
use psb_base_mod
use mld_prec_type
type(psb_dspmat_type), intent(in), target :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dspmat_type), intent(inout),target :: ac
type(psb_desc_type), intent(inout) :: desc_ac
type(psb_dspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dspmat_type), intent(out) :: ac
type(psb_desc_type), intent(out) :: desc_ac
type(mld_dbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
integer, intent(out) :: info
end subroutine mld_daggrmat_raw_asb
subroutine mld_zaggrmat_raw_asb(a,desc_a,ac,desc_ac,p,info)
use psb_base_mod
use mld_prec_type
type(psb_zspmat_type), intent(in), target :: a
type(mld_zbaseprc_type), intent(inout),target :: p
type(psb_zspmat_type), intent(inout),target :: ac
type(psb_desc_type), intent(in) :: desc_a
type(psb_desc_type), intent(inout) :: desc_ac
integer, intent(out) :: info
type(psb_zspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_zspmat_type), intent(out) :: ac
type(psb_desc_type), intent(out) :: desc_ac
type(mld_zbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
end subroutine mld_zaggrmat_raw_asb
end interface
@ -674,22 +674,22 @@ module mld_prec_mod
subroutine mld_daggrmat_smth_asb(a,desc_a,ac,desc_ac,p,info)
use psb_base_mod
use mld_prec_type
type(psb_dspmat_type), intent(in), target :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dspmat_type), intent(inout),target :: ac
type(psb_desc_type), intent(inout) :: desc_ac
type(psb_dspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dspmat_type), intent(out) :: ac
type(psb_desc_type), intent(out) :: desc_ac
type(mld_dbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
integer, intent(out) :: info
end subroutine mld_daggrmat_smth_asb
subroutine mld_zaggrmat_smth_asb(a,desc_a,ac,desc_ac,p,info)
use psb_base_mod
use mld_prec_type
type(psb_zspmat_type), intent(in), target :: a
type(mld_zbaseprc_type), intent(inout),target :: p
type(psb_zspmat_type), intent(inout),target :: ac
type(psb_desc_type), intent(in) :: desc_a
type(psb_desc_type), intent(inout) :: desc_ac
integer, intent(out) :: info
type(psb_zspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_zspmat_type), intent(out) :: ac
type(psb_desc_type), intent(out) :: desc_ac
type(mld_zbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
end subroutine mld_zaggrmat_smth_asb
end interface

@ -915,14 +915,14 @@ contains
is_legal_ml_type = ((ip>=mld_no_ml_).and.(ip<=mld_max_ml_))
return
end function is_legal_ml_type
function is_legal_ml_aggr_kind(ip)
function is_legal_ml_aggr_alg(ip)
use psb_base_mod
integer, intent(in) :: ip
logical :: is_legal_ml_aggr_kind
logical :: is_legal_ml_aggr_alg
is_legal_ml_aggr_kind = ((ip>=mld_dec_aggr_).and.(ip<=mld_max_aggr_))
is_legal_ml_aggr_alg = ((ip>=mld_dec_aggr_).and.(ip<=mld_max_aggr_))
return
end function is_legal_ml_aggr_kind
end function is_legal_ml_aggr_alg
function is_legal_ml_smooth_pos(ip)
use psb_base_mod
integer, intent(in) :: ip

@ -99,15 +99,15 @@ subroutine mld_zaggrmat_asb(a,desc_a,ac,desc_ac,p,info)
implicit none
! Arguments
type(psb_zspmat_type), intent(in), target :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_zspmat_type), intent(inout), target :: ac
type(psb_desc_type), intent(inout) :: desc_ac
type(mld_zbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
type(psb_zspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_zspmat_type), intent(out) :: ac
type(psb_desc_type), intent(out) :: desc_ac
type(mld_zbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
! Local variables
integer ::ictxt,np,me, err_act, icomm
integer :: ictxt,np,me, err_act, icomm
character(len=20) :: name
name='mld_aggrmat_asb'

@ -87,12 +87,12 @@ subroutine mld_zaggrmat_raw_asb(a,desc_a,ac,desc_ac,p,info)
#endif
! Arguments
type(psb_zspmat_type), intent(in), target :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_zspmat_type), intent(inout), target :: ac
type(psb_desc_type), intent(inout) :: desc_ac
type(mld_zbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
type(psb_zspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_zspmat_type), intent(out) :: ac
type(psb_desc_type), intent(out) :: desc_ac
type(mld_zbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
! Local variables
integer ::ictxt,np,me, err_act, icomm

@ -105,12 +105,12 @@ subroutine mld_zaggrmat_smth_asb(a,desc_a,ac,desc_ac,p,info)
#endif
! Arguments
type(psb_zspmat_type), intent(in), target :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_zspmat_type), intent(inout), target :: ac
type(psb_desc_type), intent(inout) :: desc_ac
type(mld_zbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
type(psb_zspmat_type), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_zspmat_type), intent(out) :: ac
type(psb_desc_type), intent(out) :: desc_ac
type(mld_zbaseprc_type), intent(inout), target :: p
integer, intent(out) :: info
! Local variables
type(psb_zspmat_type) :: b
@ -249,6 +249,9 @@ subroutine mld_zaggrmat_smth_asb(a,desc_a,ac,desc_ac,p,info)
call psb_errpush(4010,name,a_err='spcnv')
goto 9999
end if
if (debug_level >= psb_debug_outer_) &
& write(debug_unit,*) me,' ',trim(name),&
& ' Initial copies done.'
!
! WARNING: the cycles below assume that AM3 does have

@ -90,7 +90,7 @@ subroutine mld_zmlprec_bld(a,desc_a,p,info)
call mld_check_def(p%iprcparm(mld_ml_type_),'Multilevel type',&
& mld_mult_ml_,is_legal_ml_type)
call mld_check_def(p%iprcparm(mld_aggr_alg_),'Aggregation',&
& mld_dec_aggr_,is_legal_ml_aggr_kind)
& mld_dec_aggr_,is_legal_ml_aggr_alg)
call mld_check_def(p%iprcparm(mld_aggr_kind_),'Smoother',&
& mld_smooth_prol_,is_legal_ml_smth_kind)
call mld_check_def(p%iprcparm(mld_coarse_mat_),'Coarse matrix',&
@ -127,8 +127,6 @@ subroutine mld_zmlprec_bld(a,desc_a,p,info)
! the mapping defined by mld_aggrmap_bld and applying the aggregation
! algorithm specified by p%iprcparm(mld_aggr_kind_)
!
call psb_nullify_sp(ac)
call psb_nullify_desc(desc_ac)
call mld_aggrmat_asb(a,desc_a,ac,desc_ac,p,info)
if(info /= 0) then
call psb_errpush(4010,name,a_err='mld_aggrmat_asb')

Loading…
Cancel
Save