base/modules/psb_c_base_mat_mod.f03
 base/modules/psb_c_mat_mod.f03
 base/modules/psb_d_base_mat_mod.f03
 base/modules/psb_d_mat_mod.f03
 base/modules/psb_psblas_mod.f90
 base/modules/psb_s_base_mat_mod.f03
 base/modules/psb_s_mat_mod.f03
 base/modules/psb_z_base_mat_mod.f03
 base/modules/psb_z_mat_mod.f03
 base/psblas/psb_cspsm.f90
 base/psblas/psb_dspsm.f90
 base/psblas/psb_sspsm.f90
 base/psblas/psb_zspsm.f90
 base/serial/dp/dvtfg.f
 krylov/psb_krylov_mod.f90
 prec/psb_cbjac_aply.f90
 prec/psb_dbjac_aply.f90
 prec/psb_sbjac_aply.f90
 prec/psb_zbjac_aply.f90

Changed "SIDE" to "SCALE" in SM. 
Maybe we need to add back a PERM (Left, Right) argument somewhere???
psblas3-type-indexed
Salvatore Filippone 15 years ago
parent 233835de10
commit 8bac54b124

@ -902,7 +902,7 @@ contains
end subroutine c_base_cssv end subroutine c_base_cssv
subroutine c_cssm(alpha,a,x,beta,y,info,trans,side,d) subroutine c_cssm(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
use psb_string_mod use psb_string_mod
implicit none implicit none
@ -910,12 +910,12 @@ contains
complex(psb_spk_), intent(in) :: alpha, beta, x(:,:) complex(psb_spk_), intent(in) :: alpha, beta, x(:,:)
complex(psb_spk_), intent(inout) :: y(:,:) complex(psb_spk_), intent(inout) :: y(:,:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
complex(psb_spk_), intent(in), optional :: d(:) complex(psb_spk_), intent(in), optional :: d(:)
complex(psb_spk_), allocatable :: tmp(:,:) complex(psb_spk_), allocatable :: tmp(:,:)
Integer :: err_act, nar,nac,nc, i Integer :: err_act, nar,nac,nc, i
character(len=1) :: side_ character(len=1) :: scale_
character(len=20) :: name='c_cssm' character(len=20) :: name='c_cssm'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
@ -948,13 +948,13 @@ contains
end if end if
if (present(d)) then if (present(d)) then
if (present(side)) then if (present(scale)) then
side_ = side scale_ = scale
else else
side_ = 'L' scale_ = 'L'
end if end if
if (psb_toupper(side_) == 'R') then if (psb_toupper(scale_) == 'R') then
if (size(d,1) < nac) then if (size(d,1) < nac) then
info = 36 info = 36
call psb_errpush(info,name,i_err=(/9,nac,0,0,0/)) call psb_errpush(info,name,i_err=(/9,nac,0,0,0/))
@ -976,7 +976,7 @@ contains
if (info /= 0) info = 4000 if (info /= 0) info = 4000
end if end if
else if (psb_toupper(side_) == 'L') then else if (psb_toupper(scale_) == 'L') then
if (size(d,1) < nar) then if (size(d,1) < nar) then
info = 36 info = 36
@ -1004,11 +1004,11 @@ contains
else else
info = 31 info = 31
call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=side_) call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=scale_)
goto 9999 goto 9999
end if end if
else else
! Side is ignored in this case ! Scale is ignored in this case
call a%base_cssm(alpha,x,beta,y,info,trans) call a%base_cssm(alpha,x,beta,y,info,trans)
end if end if
@ -1036,7 +1036,7 @@ contains
end subroutine c_cssm end subroutine c_cssm
subroutine c_cssv(alpha,a,x,beta,y,info,trans,side,d) subroutine c_cssv(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
use psb_string_mod use psb_string_mod
implicit none implicit none
@ -1044,12 +1044,12 @@ contains
complex(psb_spk_), intent(in) :: alpha, beta, x(:) complex(psb_spk_), intent(in) :: alpha, beta, x(:)
complex(psb_spk_), intent(inout) :: y(:) complex(psb_spk_), intent(inout) :: y(:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
complex(psb_spk_), intent(in), optional :: d(:) complex(psb_spk_), intent(in), optional :: d(:)
complex(psb_spk_), allocatable :: tmp(:) complex(psb_spk_), allocatable :: tmp(:)
Integer :: err_act, nar,nac,nc, i Integer :: err_act, nar,nac,nc, i
character(len=1) :: side_ character(len=1) :: scale_
character(len=20) :: name='c_cssm' character(len=20) :: name='c_cssm'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
@ -1082,13 +1082,13 @@ contains
end if end if
if (present(d)) then if (present(d)) then
if (present(side)) then if (present(scale)) then
side_ = side scale_ = scale
else else
side_ = 'L' scale_ = 'L'
end if end if
if (psb_toupper(side_) == 'R') then if (psb_toupper(scale_) == 'R') then
if (size(d,1) < nac) then if (size(d,1) < nac) then
info = 36 info = 36
call psb_errpush(info,name,i_err=(/9,nac,0,0,0/)) call psb_errpush(info,name,i_err=(/9,nac,0,0,0/))
@ -1106,7 +1106,7 @@ contains
if (info /= 0) info = 4000 if (info /= 0) info = 4000
end if end if
else if (psb_toupper(side_) == 'L') then else if (psb_toupper(scale_) == 'L') then
if (size(d,1) < nar) then if (size(d,1) < nar) then
info = 36 info = 36
call psb_errpush(info,name,i_err=(/9,nar,0,0,0/)) call psb_errpush(info,name,i_err=(/9,nar,0,0,0/))
@ -1129,11 +1129,11 @@ contains
else else
info = 31 info = 31
call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=side_) call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=scale_)
goto 9999 goto 9999
end if end if
else else
! Side is ignored in this case ! Scale is ignored in this case
call a%base_cssm(alpha,x,beta,y,info,trans) call a%base_cssm(alpha,x,beta,y,info,trans)
end if end if

@ -1699,14 +1699,14 @@ contains
end subroutine c_csmv end subroutine c_csmv
subroutine c_cssm(alpha,a,x,beta,y,info,trans,side,d) subroutine c_cssm(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
implicit none implicit none
class(psb_c_sparse_mat), intent(in) :: a class(psb_c_sparse_mat), intent(in) :: a
complex(psb_spk_), intent(in) :: alpha, beta, x(:,:) complex(psb_spk_), intent(in) :: alpha, beta, x(:,:)
complex(psb_spk_), intent(inout) :: y(:,:) complex(psb_spk_), intent(inout) :: y(:,:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
complex(psb_spk_), intent(in), optional :: d(:) complex(psb_spk_), intent(in), optional :: d(:)
Integer :: err_act Integer :: err_act
character(len=20) :: name='psb_cssm' character(len=20) :: name='psb_cssm'
@ -1720,7 +1720,7 @@ contains
goto 9999 goto 9999
endif endif
call a%a%cssm(alpha,x,beta,y,info,trans,side,d) call a%a%cssm(alpha,x,beta,y,info,trans,scale,d)
if (info /= 0) goto 9999 if (info /= 0) goto 9999
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
@ -1737,14 +1737,14 @@ contains
end subroutine c_cssm end subroutine c_cssm
subroutine c_cssv(alpha,a,x,beta,y,info,trans,side,d) subroutine c_cssv(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
implicit none implicit none
class(psb_c_sparse_mat), intent(in) :: a class(psb_c_sparse_mat), intent(in) :: a
complex(psb_spk_), intent(in) :: alpha, beta, x(:) complex(psb_spk_), intent(in) :: alpha, beta, x(:)
complex(psb_spk_), intent(inout) :: y(:) complex(psb_spk_), intent(inout) :: y(:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
complex(psb_spk_), intent(in), optional :: d(:) complex(psb_spk_), intent(in), optional :: d(:)
Integer :: err_act Integer :: err_act
character(len=20) :: name='psb_cssv' character(len=20) :: name='psb_cssv'
@ -1758,7 +1758,7 @@ contains
goto 9999 goto 9999
endif endif
call a%a%cssm(alpha,x,beta,y,info,trans,side,d) call a%a%cssm(alpha,x,beta,y,info,trans,scale,d)
if (info /= 0) goto 9999 if (info /= 0) goto 9999

@ -902,7 +902,7 @@ contains
end subroutine d_base_cssv end subroutine d_base_cssv
subroutine d_cssm(alpha,a,x,beta,y,info,trans,side,d) subroutine d_cssm(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
use psb_string_mod use psb_string_mod
implicit none implicit none
@ -910,12 +910,12 @@ contains
real(psb_dpk_), intent(in) :: alpha, beta, x(:,:) real(psb_dpk_), intent(in) :: alpha, beta, x(:,:)
real(psb_dpk_), intent(inout) :: y(:,:) real(psb_dpk_), intent(inout) :: y(:,:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
real(psb_dpk_), intent(in), optional :: d(:) real(psb_dpk_), intent(in), optional :: d(:)
real(psb_dpk_), allocatable :: tmp(:,:) real(psb_dpk_), allocatable :: tmp(:,:)
Integer :: err_act, nar,nac,nc, i Integer :: err_act, nar,nac,nc, i
character(len=1) :: side_ character(len=1) :: scale_
character(len=20) :: name='d_cssm' character(len=20) :: name='d_cssm'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
@ -948,13 +948,13 @@ contains
end if end if
if (present(d)) then if (present(d)) then
if (present(side)) then if (present(scale)) then
side_ = side scale_ = scale
else else
side_ = 'L' scale_ = 'L'
end if end if
if (psb_toupper(side_) == 'R') then if (psb_toupper(scale_) == 'R') then
if (size(d,1) < nac) then if (size(d,1) < nac) then
info = 36 info = 36
call psb_errpush(info,name,i_err=(/9,nac,0,0,0/)) call psb_errpush(info,name,i_err=(/9,nac,0,0,0/))
@ -976,7 +976,7 @@ contains
if (info /= 0) info = 4000 if (info /= 0) info = 4000
end if end if
else if (psb_toupper(side_) == 'L') then else if (psb_toupper(scale_) == 'L') then
if (size(d,1) < nar) then if (size(d,1) < nar) then
info = 36 info = 36
@ -1004,11 +1004,11 @@ contains
else else
info = 31 info = 31
call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=side_) call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=scale_)
goto 9999 goto 9999
end if end if
else else
! Side is ignored in this case ! Scale is ignored in this case
call a%base_cssm(alpha,x,beta,y,info,trans) call a%base_cssm(alpha,x,beta,y,info,trans)
end if end if
@ -1036,7 +1036,7 @@ contains
end subroutine d_cssm end subroutine d_cssm
subroutine d_cssv(alpha,a,x,beta,y,info,trans,side,d) subroutine d_cssv(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
use psb_string_mod use psb_string_mod
implicit none implicit none
@ -1044,12 +1044,12 @@ contains
real(psb_dpk_), intent(in) :: alpha, beta, x(:) real(psb_dpk_), intent(in) :: alpha, beta, x(:)
real(psb_dpk_), intent(inout) :: y(:) real(psb_dpk_), intent(inout) :: y(:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
real(psb_dpk_), intent(in), optional :: d(:) real(psb_dpk_), intent(in), optional :: d(:)
real(psb_dpk_), allocatable :: tmp(:) real(psb_dpk_), allocatable :: tmp(:)
Integer :: err_act, nar,nac,nc, i Integer :: err_act, nar,nac,nc, i
character(len=1) :: side_ character(len=1) :: scale_
character(len=20) :: name='d_cssm' character(len=20) :: name='d_cssm'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
@ -1082,13 +1082,13 @@ contains
end if end if
if (present(d)) then if (present(d)) then
if (present(side)) then if (present(scale)) then
side_ = side scale_ = scale
else else
side_ = 'L' scale_ = 'L'
end if end if
if (psb_toupper(side_) == 'R') then if (psb_toupper(scale_) == 'R') then
if (size(d,1) < nac) then if (size(d,1) < nac) then
info = 36 info = 36
call psb_errpush(info,name,i_err=(/9,nac,0,0,0/)) call psb_errpush(info,name,i_err=(/9,nac,0,0,0/))
@ -1106,7 +1106,7 @@ contains
if (info /= 0) info = 4000 if (info /= 0) info = 4000
end if end if
else if (psb_toupper(side_) == 'L') then else if (psb_toupper(scale_) == 'L') then
if (size(d,1) < nar) then if (size(d,1) < nar) then
info = 36 info = 36
call psb_errpush(info,name,i_err=(/9,nar,0,0,0/)) call psb_errpush(info,name,i_err=(/9,nar,0,0,0/))
@ -1129,11 +1129,11 @@ contains
else else
info = 31 info = 31
call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=side_) call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=scale_)
goto 9999 goto 9999
end if end if
else else
! Side is ignored in this case ! Scale is ignored in this case
call a%base_cssm(alpha,x,beta,y,info,trans) call a%base_cssm(alpha,x,beta,y,info,trans)
end if end if

@ -1699,14 +1699,14 @@ contains
end subroutine d_csmv end subroutine d_csmv
subroutine d_cssm(alpha,a,x,beta,y,info,trans,side,d) subroutine d_cssm(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
implicit none implicit none
class(psb_d_sparse_mat), intent(in) :: a class(psb_d_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(in) :: alpha, beta, x(:,:) real(psb_dpk_), intent(in) :: alpha, beta, x(:,:)
real(psb_dpk_), intent(inout) :: y(:,:) real(psb_dpk_), intent(inout) :: y(:,:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
real(psb_dpk_), intent(in), optional :: d(:) real(psb_dpk_), intent(in), optional :: d(:)
Integer :: err_act Integer :: err_act
character(len=20) :: name='psb_cssm' character(len=20) :: name='psb_cssm'
@ -1720,7 +1720,7 @@ contains
goto 9999 goto 9999
endif endif
call a%a%cssm(alpha,x,beta,y,info,trans,side,d) call a%a%cssm(alpha,x,beta,y,info,trans,scale,d)
if (info /= 0) goto 9999 if (info /= 0) goto 9999
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
@ -1737,14 +1737,14 @@ contains
end subroutine d_cssm end subroutine d_cssm
subroutine d_cssv(alpha,a,x,beta,y,info,trans,side,d) subroutine d_cssv(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
implicit none implicit none
class(psb_d_sparse_mat), intent(in) :: a class(psb_d_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(in) :: alpha, beta, x(:) real(psb_dpk_), intent(in) :: alpha, beta, x(:)
real(psb_dpk_), intent(inout) :: y(:) real(psb_dpk_), intent(inout) :: y(:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
real(psb_dpk_), intent(in), optional :: d(:) real(psb_dpk_), intent(in), optional :: d(:)
Integer :: err_act Integer :: err_act
character(len=20) :: name='psb_cssv' character(len=20) :: name='psb_cssv'
@ -1758,7 +1758,7 @@ contains
goto 9999 goto 9999
endif endif
call a%a%cssm(alpha,x,beta,y,info,trans,side,d) call a%a%cssm(alpha,x,beta,y,info,trans,scale,d)
if (info /= 0) goto 9999 if (info /= 0) goto 9999

@ -745,7 +745,7 @@ module psb_psblas_mod
interface psb_spsm interface psb_spsm
subroutine psb_sspsm(alpha, t, x, beta, y,& subroutine psb_sspsm(alpha, t, x, beta, y,&
& desc_a, info, trans, side, choice,& & desc_a, info, trans, scale, choice,&
& diag, n, jx, jy, work) & diag, n, jx, jy, work)
use psb_serial_mod use psb_serial_mod
use psb_descriptor_type use psb_descriptor_type
@ -755,14 +755,14 @@ module psb_psblas_mod
real(psb_spk_), intent(inout) :: y(:,:) real(psb_spk_), intent(inout) :: y(:,:)
real(psb_spk_), intent(in) :: alpha, beta real(psb_spk_), intent(in) :: alpha, beta
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
integer, optional, intent(in) :: n, jx, jy integer, optional, intent(in) :: n, jx, jy
integer, optional, intent(in) :: choice integer, optional, intent(in) :: choice
real(psb_spk_), optional, intent(in),target :: work(:), diag(:) real(psb_spk_), optional, intent(in),target :: work(:), diag(:)
integer, intent(out) :: info integer, intent(out) :: info
end subroutine psb_sspsm end subroutine psb_sspsm
subroutine psb_sspsv(alpha, t, x, beta, y,& subroutine psb_sspsv(alpha, t, x, beta, y,&
& desc_a, info, trans, side, choice,& & desc_a, info, trans, scale, choice,&
& diag, work) & diag, work)
use psb_serial_mod use psb_serial_mod
use psb_descriptor_type use psb_descriptor_type
@ -772,13 +772,13 @@ module psb_psblas_mod
real(psb_spk_), intent(inout) :: y(:) real(psb_spk_), intent(inout) :: y(:)
real(psb_spk_), intent(in) :: alpha, beta real(psb_spk_), intent(in) :: alpha, beta
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
integer, optional, intent(in) :: choice integer, optional, intent(in) :: choice
real(psb_spk_), optional, intent(in),target :: work(:), diag(:) real(psb_spk_), optional, intent(in),target :: work(:), diag(:)
integer, intent(out) :: info integer, intent(out) :: info
end subroutine psb_sspsv end subroutine psb_sspsv
subroutine psb_dspsm(alpha, t, x, beta, y,& subroutine psb_dspsm(alpha, t, x, beta, y,&
& desc_a, info, trans, side, choice,& & desc_a, info, trans, scale, choice,&
& diag, n, jx, jy, work) & diag, n, jx, jy, work)
use psb_serial_mod use psb_serial_mod
use psb_descriptor_type use psb_descriptor_type
@ -788,14 +788,14 @@ module psb_psblas_mod
real(psb_dpk_), intent(inout) :: y(:,:) real(psb_dpk_), intent(inout) :: y(:,:)
real(psb_dpk_), intent(in) :: alpha, beta real(psb_dpk_), intent(in) :: alpha, beta
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
integer, optional, intent(in) :: n, jx, jy integer, optional, intent(in) :: n, jx, jy
integer, optional, intent(in) :: choice integer, optional, intent(in) :: choice
real(psb_dpk_), optional, intent(in),target :: work(:), diag(:) real(psb_dpk_), optional, intent(in),target :: work(:), diag(:)
integer, intent(out) :: info integer, intent(out) :: info
end subroutine psb_dspsm end subroutine psb_dspsm
subroutine psb_dspsv(alpha, t, x, beta, y,& subroutine psb_dspsv(alpha, t, x, beta, y,&
& desc_a, info, trans, side, choice,& & desc_a, info, trans, scale, choice,&
& diag, work) & diag, work)
use psb_serial_mod use psb_serial_mod
use psb_descriptor_type use psb_descriptor_type
@ -805,13 +805,13 @@ module psb_psblas_mod
real(psb_dpk_), intent(inout) :: y(:) real(psb_dpk_), intent(inout) :: y(:)
real(psb_dpk_), intent(in) :: alpha, beta real(psb_dpk_), intent(in) :: alpha, beta
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
integer, optional, intent(in) :: choice integer, optional, intent(in) :: choice
real(psb_dpk_), optional, intent(in),target :: work(:), diag(:) real(psb_dpk_), optional, intent(in),target :: work(:), diag(:)
integer, intent(out) :: info integer, intent(out) :: info
end subroutine psb_dspsv end subroutine psb_dspsv
subroutine psb_cspsm(alpha, t, x, beta, y,& subroutine psb_cspsm(alpha, t, x, beta, y,&
& desc_a, info, trans, side, choice,& & desc_a, info, trans, scale, choice,&
& diag, n, jx, jy, work) & diag, n, jx, jy, work)
use psb_serial_mod use psb_serial_mod
use psb_descriptor_type use psb_descriptor_type
@ -821,14 +821,14 @@ module psb_psblas_mod
complex(psb_spk_), intent(inout) :: y(:,:) complex(psb_spk_), intent(inout) :: y(:,:)
complex(psb_spk_), intent(in) :: alpha, beta complex(psb_spk_), intent(in) :: alpha, beta
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
integer, optional, intent(in) :: n, jx, jy integer, optional, intent(in) :: n, jx, jy
integer, optional, intent(in) :: choice integer, optional, intent(in) :: choice
complex(psb_spk_), optional, intent(in),target :: work(:), diag(:) complex(psb_spk_), optional, intent(in),target :: work(:), diag(:)
integer, intent(out) :: info integer, intent(out) :: info
end subroutine psb_cspsm end subroutine psb_cspsm
subroutine psb_cspsv(alpha, t, x, beta, y,& subroutine psb_cspsv(alpha, t, x, beta, y,&
& desc_a, info, trans, side, choice,& & desc_a, info, trans, scale, choice,&
& diag, work) & diag, work)
use psb_serial_mod use psb_serial_mod
use psb_descriptor_type use psb_descriptor_type
@ -838,13 +838,13 @@ module psb_psblas_mod
complex(psb_spk_), intent(inout) :: y(:) complex(psb_spk_), intent(inout) :: y(:)
complex(psb_spk_), intent(in) :: alpha, beta complex(psb_spk_), intent(in) :: alpha, beta
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
integer, optional, intent(in) :: choice integer, optional, intent(in) :: choice
complex(psb_spk_), optional, intent(in),target :: work(:), diag(:) complex(psb_spk_), optional, intent(in),target :: work(:), diag(:)
integer, intent(out) :: info integer, intent(out) :: info
end subroutine psb_cspsv end subroutine psb_cspsv
subroutine psb_zspsm(alpha, t, x, beta, y,& subroutine psb_zspsm(alpha, t, x, beta, y,&
& desc_a, info, trans, side, choice,& & desc_a, info, trans, scale, choice,&
& diag, n, jx, jy, work) & diag, n, jx, jy, work)
use psb_serial_mod use psb_serial_mod
use psb_descriptor_type use psb_descriptor_type
@ -854,14 +854,14 @@ module psb_psblas_mod
complex(psb_dpk_), intent(inout) :: y(:,:) complex(psb_dpk_), intent(inout) :: y(:,:)
complex(psb_dpk_), intent(in) :: alpha, beta complex(psb_dpk_), intent(in) :: alpha, beta
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
integer, optional, intent(in) :: n, jx, jy integer, optional, intent(in) :: n, jx, jy
integer, optional, intent(in) :: choice integer, optional, intent(in) :: choice
complex(psb_dpk_), optional, intent(in),target :: work(:), diag(:) complex(psb_dpk_), optional, intent(in),target :: work(:), diag(:)
integer, intent(out) :: info integer, intent(out) :: info
end subroutine psb_zspsm end subroutine psb_zspsm
subroutine psb_zspsv(alpha, t, x, beta, y,& subroutine psb_zspsv(alpha, t, x, beta, y,&
& desc_a, info, trans, side, choice,& & desc_a, info, trans, scale, choice,&
& diag, work) & diag, work)
use psb_serial_mod use psb_serial_mod
use psb_descriptor_type use psb_descriptor_type
@ -871,7 +871,7 @@ module psb_psblas_mod
complex(psb_dpk_), intent(inout) :: y(:) complex(psb_dpk_), intent(inout) :: y(:)
complex(psb_dpk_), intent(in) :: alpha, beta complex(psb_dpk_), intent(in) :: alpha, beta
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
integer, optional, intent(in) :: choice integer, optional, intent(in) :: choice
complex(psb_dpk_), optional, intent(in),target :: work(:), diag(:) complex(psb_dpk_), optional, intent(in),target :: work(:), diag(:)
integer, intent(out) :: info integer, intent(out) :: info

@ -902,7 +902,7 @@ contains
end subroutine s_base_cssv end subroutine s_base_cssv
subroutine s_cssm(alpha,a,x,beta,y,info,trans,side,d) subroutine s_cssm(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
use psb_string_mod use psb_string_mod
implicit none implicit none
@ -910,12 +910,12 @@ contains
real(psb_spk_), intent(in) :: alpha, beta, x(:,:) real(psb_spk_), intent(in) :: alpha, beta, x(:,:)
real(psb_spk_), intent(inout) :: y(:,:) real(psb_spk_), intent(inout) :: y(:,:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
real(psb_spk_), intent(in), optional :: d(:) real(psb_spk_), intent(in), optional :: d(:)
real(psb_spk_), allocatable :: tmp(:,:) real(psb_spk_), allocatable :: tmp(:,:)
Integer :: err_act, nar,nac,nc, i Integer :: err_act, nar,nac,nc, i
character(len=1) :: side_ character(len=1) :: scale_
character(len=20) :: name='s_cssm' character(len=20) :: name='s_cssm'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
@ -948,13 +948,13 @@ contains
end if end if
if (present(d)) then if (present(d)) then
if (present(side)) then if (present(scale)) then
side_ = side scale_ = scale
else else
side_ = 'L' scale_ = 'L'
end if end if
if (psb_toupper(side_) == 'R') then if (psb_toupper(scale_) == 'R') then
if (size(d,1) < nac) then if (size(d,1) < nac) then
info = 36 info = 36
call psb_errpush(info,name,i_err=(/9,nac,0,0,0/)) call psb_errpush(info,name,i_err=(/9,nac,0,0,0/))
@ -976,7 +976,7 @@ contains
if (info /= 0) info = 4000 if (info /= 0) info = 4000
end if end if
else if (psb_toupper(side_) == 'L') then else if (psb_toupper(scale_) == 'L') then
if (size(d,1) < nar) then if (size(d,1) < nar) then
info = 36 info = 36
@ -1004,11 +1004,11 @@ contains
else else
info = 31 info = 31
call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=side_) call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=scale_)
goto 9999 goto 9999
end if end if
else else
! Side is ignored in this case ! Scale is ignored in this case
call a%base_cssm(alpha,x,beta,y,info,trans) call a%base_cssm(alpha,x,beta,y,info,trans)
end if end if
@ -1036,7 +1036,7 @@ contains
end subroutine s_cssm end subroutine s_cssm
subroutine s_cssv(alpha,a,x,beta,y,info,trans,side,d) subroutine s_cssv(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
use psb_string_mod use psb_string_mod
implicit none implicit none
@ -1044,12 +1044,12 @@ contains
real(psb_spk_), intent(in) :: alpha, beta, x(:) real(psb_spk_), intent(in) :: alpha, beta, x(:)
real(psb_spk_), intent(inout) :: y(:) real(psb_spk_), intent(inout) :: y(:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
real(psb_spk_), intent(in), optional :: d(:) real(psb_spk_), intent(in), optional :: d(:)
real(psb_spk_), allocatable :: tmp(:) real(psb_spk_), allocatable :: tmp(:)
Integer :: err_act, nar,nac,nc, i Integer :: err_act, nar,nac,nc, i
character(len=1) :: side_ character(len=1) :: scale_
character(len=20) :: name='s_cssm' character(len=20) :: name='s_cssm'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
@ -1082,13 +1082,13 @@ contains
end if end if
if (present(d)) then if (present(d)) then
if (present(side)) then if (present(scale)) then
side_ = side scale_ = scale
else else
side_ = 'L' scale_ = 'L'
end if end if
if (psb_toupper(side_) == 'R') then if (psb_toupper(scale_) == 'R') then
if (size(d,1) < nac) then if (size(d,1) < nac) then
info = 36 info = 36
call psb_errpush(info,name,i_err=(/9,nac,0,0,0/)) call psb_errpush(info,name,i_err=(/9,nac,0,0,0/))
@ -1106,7 +1106,7 @@ contains
if (info /= 0) info = 4000 if (info /= 0) info = 4000
end if end if
else if (psb_toupper(side_) == 'L') then else if (psb_toupper(scale_) == 'L') then
if (size(d,1) < nar) then if (size(d,1) < nar) then
info = 36 info = 36
call psb_errpush(info,name,i_err=(/9,nar,0,0,0/)) call psb_errpush(info,name,i_err=(/9,nar,0,0,0/))
@ -1129,11 +1129,11 @@ contains
else else
info = 31 info = 31
call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=side_) call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=scale_)
goto 9999 goto 9999
end if end if
else else
! Side is ignored in this case ! Scale is ignored in this case
call a%base_cssm(alpha,x,beta,y,info,trans) call a%base_cssm(alpha,x,beta,y,info,trans)
end if end if

@ -1699,14 +1699,14 @@ contains
end subroutine s_csmv end subroutine s_csmv
subroutine s_cssm(alpha,a,x,beta,y,info,trans,side,d) subroutine s_cssm(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
implicit none implicit none
class(psb_s_sparse_mat), intent(in) :: a class(psb_s_sparse_mat), intent(in) :: a
real(psb_spk_), intent(in) :: alpha, beta, x(:,:) real(psb_spk_), intent(in) :: alpha, beta, x(:,:)
real(psb_spk_), intent(inout) :: y(:,:) real(psb_spk_), intent(inout) :: y(:,:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
real(psb_spk_), intent(in), optional :: d(:) real(psb_spk_), intent(in), optional :: d(:)
Integer :: err_act Integer :: err_act
character(len=20) :: name='psb_cssm' character(len=20) :: name='psb_cssm'
@ -1720,7 +1720,7 @@ contains
goto 9999 goto 9999
endif endif
call a%a%cssm(alpha,x,beta,y,info,trans,side,d) call a%a%cssm(alpha,x,beta,y,info,trans,scale,d)
if (info /= 0) goto 9999 if (info /= 0) goto 9999
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
@ -1737,14 +1737,14 @@ contains
end subroutine s_cssm end subroutine s_cssm
subroutine s_cssv(alpha,a,x,beta,y,info,trans,side,d) subroutine s_cssv(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
implicit none implicit none
class(psb_s_sparse_mat), intent(in) :: a class(psb_s_sparse_mat), intent(in) :: a
real(psb_spk_), intent(in) :: alpha, beta, x(:) real(psb_spk_), intent(in) :: alpha, beta, x(:)
real(psb_spk_), intent(inout) :: y(:) real(psb_spk_), intent(inout) :: y(:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
real(psb_spk_), intent(in), optional :: d(:) real(psb_spk_), intent(in), optional :: d(:)
Integer :: err_act Integer :: err_act
character(len=20) :: name='psb_cssv' character(len=20) :: name='psb_cssv'
@ -1758,7 +1758,7 @@ contains
goto 9999 goto 9999
endif endif
call a%a%cssm(alpha,x,beta,y,info,trans,side,d) call a%a%cssm(alpha,x,beta,y,info,trans,scale,d)
if (info /= 0) goto 9999 if (info /= 0) goto 9999

@ -902,7 +902,7 @@ contains
end subroutine z_base_cssv end subroutine z_base_cssv
subroutine z_cssm(alpha,a,x,beta,y,info,trans,side,d) subroutine z_cssm(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
use psb_string_mod use psb_string_mod
implicit none implicit none
@ -910,12 +910,12 @@ contains
complex(psb_dpk_), intent(in) :: alpha, beta, x(:,:) complex(psb_dpk_), intent(in) :: alpha, beta, x(:,:)
complex(psb_dpk_), intent(inout) :: y(:,:) complex(psb_dpk_), intent(inout) :: y(:,:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
complex(psb_dpk_), intent(in), optional :: d(:) complex(psb_dpk_), intent(in), optional :: d(:)
complex(psb_dpk_), allocatable :: tmp(:,:) complex(psb_dpk_), allocatable :: tmp(:,:)
Integer :: err_act, nar,nac,nc, i Integer :: err_act, nar,nac,nc, i
character(len=1) :: side_ character(len=1) :: scale_
character(len=20) :: name='z_cssm' character(len=20) :: name='z_cssm'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
@ -948,13 +948,13 @@ contains
end if end if
if (present(d)) then if (present(d)) then
if (present(side)) then if (present(scale)) then
side_ = side scale_ = scale
else else
side_ = 'L' scale_ = 'L'
end if end if
if (psb_toupper(side_) == 'R') then if (psb_toupper(scale_) == 'R') then
if (size(d,1) < nac) then if (size(d,1) < nac) then
info = 36 info = 36
call psb_errpush(info,name,i_err=(/9,nac,0,0,0/)) call psb_errpush(info,name,i_err=(/9,nac,0,0,0/))
@ -976,7 +976,7 @@ contains
if (info /= 0) info = 4000 if (info /= 0) info = 4000
end if end if
else if (psb_toupper(side_) == 'L') then else if (psb_toupper(scale_) == 'L') then
if (size(d,1) < nar) then if (size(d,1) < nar) then
info = 36 info = 36
@ -1004,11 +1004,11 @@ contains
else else
info = 31 info = 31
call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=side_) call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=scale_)
goto 9999 goto 9999
end if end if
else else
! Side is ignored in this case ! Scale is ignored in this case
call a%base_cssm(alpha,x,beta,y,info,trans) call a%base_cssm(alpha,x,beta,y,info,trans)
end if end if
@ -1036,7 +1036,7 @@ contains
end subroutine z_cssm end subroutine z_cssm
subroutine z_cssv(alpha,a,x,beta,y,info,trans,side,d) subroutine z_cssv(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
use psb_string_mod use psb_string_mod
implicit none implicit none
@ -1044,12 +1044,12 @@ contains
complex(psb_dpk_), intent(in) :: alpha, beta, x(:) complex(psb_dpk_), intent(in) :: alpha, beta, x(:)
complex(psb_dpk_), intent(inout) :: y(:) complex(psb_dpk_), intent(inout) :: y(:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
complex(psb_dpk_), intent(in), optional :: d(:) complex(psb_dpk_), intent(in), optional :: d(:)
complex(psb_dpk_), allocatable :: tmp(:) complex(psb_dpk_), allocatable :: tmp(:)
Integer :: err_act, nar,nac,nc, i Integer :: err_act, nar,nac,nc, i
character(len=1) :: side_ character(len=1) :: scale_
character(len=20) :: name='z_cssm' character(len=20) :: name='z_cssm'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
@ -1082,13 +1082,13 @@ contains
end if end if
if (present(d)) then if (present(d)) then
if (present(side)) then if (present(scale)) then
side_ = side scale_ = scale
else else
side_ = 'L' scale_ = 'L'
end if end if
if (psb_toupper(side_) == 'R') then if (psb_toupper(scale_) == 'R') then
if (size(d,1) < nac) then if (size(d,1) < nac) then
info = 36 info = 36
call psb_errpush(info,name,i_err=(/9,nac,0,0,0/)) call psb_errpush(info,name,i_err=(/9,nac,0,0,0/))
@ -1106,7 +1106,7 @@ contains
if (info /= 0) info = 4000 if (info /= 0) info = 4000
end if end if
else if (psb_toupper(side_) == 'L') then else if (psb_toupper(scale_) == 'L') then
if (size(d,1) < nar) then if (size(d,1) < nar) then
info = 36 info = 36
call psb_errpush(info,name,i_err=(/9,nar,0,0,0/)) call psb_errpush(info,name,i_err=(/9,nar,0,0,0/))
@ -1129,11 +1129,11 @@ contains
else else
info = 31 info = 31
call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=side_) call psb_errpush(info,name,i_err=(/8,0,0,0,0/),a_err=scale_)
goto 9999 goto 9999
end if end if
else else
! Side is ignored in this case ! Scale is ignored in this case
call a%base_cssm(alpha,x,beta,y,info,trans) call a%base_cssm(alpha,x,beta,y,info,trans)
end if end if

@ -1699,14 +1699,14 @@ contains
end subroutine z_csmv end subroutine z_csmv
subroutine z_cssm(alpha,a,x,beta,y,info,trans,side,d) subroutine z_cssm(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
implicit none implicit none
class(psb_z_sparse_mat), intent(in) :: a class(psb_z_sparse_mat), intent(in) :: a
complex(psb_dpk_), intent(in) :: alpha, beta, x(:,:) complex(psb_dpk_), intent(in) :: alpha, beta, x(:,:)
complex(psb_dpk_), intent(inout) :: y(:,:) complex(psb_dpk_), intent(inout) :: y(:,:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
complex(psb_dpk_), intent(in), optional :: d(:) complex(psb_dpk_), intent(in), optional :: d(:)
Integer :: err_act Integer :: err_act
character(len=20) :: name='psb_cssm' character(len=20) :: name='psb_cssm'
@ -1720,7 +1720,7 @@ contains
goto 9999 goto 9999
endif endif
call a%a%cssm(alpha,x,beta,y,info,trans,side,d) call a%a%cssm(alpha,x,beta,y,info,trans,scale,d)
if (info /= 0) goto 9999 if (info /= 0) goto 9999
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
@ -1737,14 +1737,14 @@ contains
end subroutine z_cssm end subroutine z_cssm
subroutine z_cssv(alpha,a,x,beta,y,info,trans,side,d) subroutine z_cssv(alpha,a,x,beta,y,info,trans,scale,d)
use psb_error_mod use psb_error_mod
implicit none implicit none
class(psb_z_sparse_mat), intent(in) :: a class(psb_z_sparse_mat), intent(in) :: a
complex(psb_dpk_), intent(in) :: alpha, beta, x(:) complex(psb_dpk_), intent(in) :: alpha, beta, x(:)
complex(psb_dpk_), intent(inout) :: y(:) complex(psb_dpk_), intent(inout) :: y(:)
integer, intent(out) :: info integer, intent(out) :: info
character, optional, intent(in) :: trans, side character, optional, intent(in) :: trans, scale
complex(psb_dpk_), intent(in), optional :: d(:) complex(psb_dpk_), intent(in), optional :: d(:)
Integer :: err_act Integer :: err_act
character(len=20) :: name='psb_cssv' character(len=20) :: name='psb_cssv'
@ -1758,7 +1758,7 @@ contains
goto 9999 goto 9999
endif endif
call a%a%cssm(alpha,x,beta,y,info,trans,side,d) call a%a%cssm(alpha,x,beta,y,info,trans,scale,d)
if (info /= 0) goto 9999 if (info /= 0) goto 9999

@ -64,7 +64,7 @@
! desc_a - type(psb_desc_type). The communication descriptor. ! desc_a - type(psb_desc_type). The communication descriptor.
! info - integer. Return code ! info - integer. Return code
! trans - character(optional). Whether A or A'. If not present 'N' is assumed. ! trans - character(optional). Whether A or A'. If not present 'N' is assumed.
! side - character(optional). Specify some type of operation with ! scale - character(optional). Specify some type of operation with
! the diagonal matrix D. ! the diagonal matrix D.
! choice - integer(optional). The kind of update to perform on overlap elements. ! choice - integer(optional). The kind of update to perform on overlap elements.
! d(:) - complex, optional Matrix for diagonal scaling. ! d(:) - complex, optional Matrix for diagonal scaling.
@ -74,7 +74,7 @@
! work(:) - complex, optional Working area. ! work(:) - complex, optional Working area.
! !
subroutine psb_cspsm(alpha,a,x,beta,y,desc_a,info,& subroutine psb_cspsm(alpha,a,x,beta,y,desc_a,info,&
& trans, side, choice, diag, k, jx, jy, work) & trans, scale, choice, diag, k, jx, jy, work)
use psb_descriptor_type use psb_descriptor_type
use psb_comm_mod use psb_comm_mod
@ -94,7 +94,7 @@ subroutine psb_cspsm(alpha,a,x,beta,y,desc_a,info,&
integer, intent(out) :: info integer, intent(out) :: info
complex(psb_spk_), intent(in), optional, target :: diag(:) complex(psb_spk_), intent(in), optional, target :: diag(:)
complex(psb_spk_), optional, target :: work(:) complex(psb_spk_), optional, target :: work(:)
character, intent(in), optional :: trans, side character, intent(in), optional :: trans, scale
integer, intent(in), optional :: choice integer, intent(in), optional :: choice
integer, intent(in), optional :: k, jx, jy integer, intent(in), optional :: k, jx, jy
@ -104,7 +104,7 @@ subroutine psb_cspsm(alpha,a,x,beta,y,desc_a,info,&
& ix, iy, ik, ijx, ijy, i, lld,& & ix, iy, ik, ijx, ijy, i, lld,&
& m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm & m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm
character :: lside character :: lscale
integer, parameter :: nb=4 integer, parameter :: nb=4
complex(psb_spk_),pointer :: iwork(:), xp(:,:), yp(:,:), id(:) complex(psb_spk_),pointer :: iwork(:), xp(:,:), yp(:,:), id(:)
character :: itrans character :: itrans
@ -156,10 +156,10 @@ subroutine psb_cspsm(alpha,a,x,beta,y,desc_a,info,&
choice_ = psb_avg_ choice_ = psb_avg_
endif endif
if (present(side)) then if (present(scale)) then
lside = psb_toupper(side) lscale = psb_toupper(scale)
else else
lside = 'U' lscale = 'U'
endif endif
if (present(trans)) then if (present(trans)) then
@ -255,7 +255,7 @@ subroutine psb_cspsm(alpha,a,x,beta,y,desc_a,info,&
! Perform local triangular system solve ! Perform local triangular system solve
xp => x(iix:lldx,jjx:jjx+ik-1) xp => x(iix:lldx,jjx:jjx+ik-1)
yp => y(iiy:lldy,jjy:jjy+ik-1) yp => y(iiy:lldy,jjy:jjy+ik-1)
call psb_cssm(alpha,a,xp,beta,yp,info,side=side,d=diag,trans=trans) call psb_cssm(alpha,a,xp,beta,yp,info,scale=scale,d=diag,trans=trans)
if(info /= 0) then if(info /= 0) then
info = 4010 info = 4010
@ -353,14 +353,14 @@ end subroutine psb_cspsm
! desc_a - type(psb_desc_type). The communication descriptor. ! desc_a - type(psb_desc_type). The communication descriptor.
! info - integer. Return code ! info - integer. Return code
! trans - character(optional). Whether A or A'. If not present 'N' is assumed. ! trans - character(optional). Whether A or A'. If not present 'N' is assumed.
! side - character(optional). Specify some type of operation with ! scale - character(optional). Specify some type of operation with
! the diagonal matrix D. ! the diagonal matrix D.
! choice - integer(optional). The kind of update to perform on overlap elements. ! choice - integer(optional). The kind of update to perform on overlap elements.
! d(:) - complex, optional Matrix for diagonal scaling. ! d(:) - complex, optional Matrix for diagonal scaling.
! work(:) - complex, optional Working area. ! work(:) - complex, optional Working area.
! !
subroutine psb_cspsv(alpha,a,x,beta,y,desc_a,info,& subroutine psb_cspsv(alpha,a,x,beta,y,desc_a,info,&
& trans, side, choice, diag, work) & trans, scale, choice, diag, work)
use psb_descriptor_type use psb_descriptor_type
use psb_comm_mod use psb_comm_mod
use psi_mod use psi_mod
@ -379,7 +379,7 @@ subroutine psb_cspsv(alpha,a,x,beta,y,desc_a,info,&
integer, intent(out) :: info integer, intent(out) :: info
complex(psb_spk_), intent(in), optional, target :: diag(:) complex(psb_spk_), intent(in), optional, target :: diag(:)
complex(psb_spk_), optional, target :: work(:) complex(psb_spk_), optional, target :: work(:)
character, intent(in), optional :: trans, side character, intent(in), optional :: trans, scale
integer, intent(in), optional :: choice integer, intent(in), optional :: choice
! locals ! locals
@ -388,7 +388,7 @@ subroutine psb_cspsv(alpha,a,x,beta,y,desc_a,info,&
& ix, iy, ik, jx, jy, i, lld,& & ix, iy, ik, jx, jy, i, lld,&
& m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm & m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm
character :: lside character :: lscale
integer, parameter :: nb=4 integer, parameter :: nb=4
complex(psb_spk_),pointer :: iwork(:), xp(:), yp(:), id(:) complex(psb_spk_),pointer :: iwork(:), xp(:), yp(:), id(:)
character :: itrans character :: itrans
@ -424,10 +424,10 @@ subroutine psb_cspsv(alpha,a,x,beta,y,desc_a,info,&
choice_ = psb_avg_ choice_ = psb_avg_
endif endif
if (present(side)) then if (present(scale)) then
lside = psb_toupper(side) lscale = psb_toupper(scale)
else else
lside = 'U' lscale = 'U'
endif endif
if (present(trans)) then if (present(trans)) then
@ -524,7 +524,7 @@ subroutine psb_cspsv(alpha,a,x,beta,y,desc_a,info,&
! Perform local triangular system solve ! Perform local triangular system solve
xp => x(iix:lldx) xp => x(iix:lldx)
yp => y(iiy:lldy) yp => y(iiy:lldy)
call psb_cssm(alpha,a,xp,beta,yp,info,side=side,d=diag,trans=trans) call psb_cssm(alpha,a,xp,beta,yp,info,scale=scale,d=diag,trans=trans)
if(info /= 0) then if(info /= 0) then
info = 4010 info = 4010

@ -64,7 +64,7 @@
! desc_a - type(psb_desc_type). The communication descriptor. ! desc_a - type(psb_desc_type). The communication descriptor.
! info - integer. Return code ! info - integer. Return code
! trans - character(optional). Whether A or A'. If not present 'N' is assumed. ! trans - character(optional). Whether A or A'. If not present 'N' is assumed.
! side - character(optional). Specify some type of operation with ! scale - character(optional). Specify some type of operation with
! the diagonal matrix D. ! the diagonal matrix D.
! choice - integer(optional). The kind of update to perform on overlap elements. ! choice - integer(optional). The kind of update to perform on overlap elements.
! d(:) - real , optional Matrix for diagonal scaling. ! d(:) - real , optional Matrix for diagonal scaling.
@ -75,7 +75,7 @@
! !
! !
subroutine psb_dspsm(alpha,a,x,beta,y,desc_a,info,& subroutine psb_dspsm(alpha,a,x,beta,y,desc_a,info,&
& trans, side, choice, diag, k, jx, jy, work) & trans, scale, choice, diag, k, jx, jy, work)
use psb_descriptor_type use psb_descriptor_type
use psb_comm_mod use psb_comm_mod
@ -95,7 +95,7 @@ subroutine psb_dspsm(alpha,a,x,beta,y,desc_a,info,&
integer, intent(out) :: info integer, intent(out) :: info
real(psb_dpk_), intent(in), optional, target :: diag(:) real(psb_dpk_), intent(in), optional, target :: diag(:)
real(psb_dpk_), optional, target :: work(:) real(psb_dpk_), optional, target :: work(:)
character, intent(in), optional :: trans, side character, intent(in), optional :: trans, scale
integer, intent(in), optional :: choice integer, intent(in), optional :: choice
integer, intent(in), optional :: k, jx, jy integer, intent(in), optional :: k, jx, jy
@ -105,7 +105,7 @@ subroutine psb_dspsm(alpha,a,x,beta,y,desc_a,info,&
& ix, iy, ik, ijx, ijy, i, lld,& & ix, iy, ik, ijx, ijy, i, lld,&
& m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm & m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm
character :: lside character :: lscale
integer, parameter :: nb=4 integer, parameter :: nb=4
real(psb_dpk_),pointer :: iwork(:), xp(:,:), yp(:,:), id(:) real(psb_dpk_),pointer :: iwork(:), xp(:,:), yp(:,:), id(:)
character :: itrans character :: itrans
@ -157,10 +157,10 @@ subroutine psb_dspsm(alpha,a,x,beta,y,desc_a,info,&
choice_ = psb_avg_ choice_ = psb_avg_
endif endif
if (present(side)) then if (present(scale)) then
lside = psb_toupper(side) lscale = psb_toupper(scale)
else else
lside = 'U' lscale = 'U'
endif endif
if (present(trans)) then if (present(trans)) then
@ -256,7 +256,7 @@ subroutine psb_dspsm(alpha,a,x,beta,y,desc_a,info,&
! Perform local triangular system solve ! Perform local triangular system solve
xp => x(iix:lldx,jjx:jjx+ik-1) xp => x(iix:lldx,jjx:jjx+ik-1)
yp => y(iiy:lldy,jjy:jjy+ik-1) yp => y(iiy:lldy,jjy:jjy+ik-1)
call psb_cssm(alpha,a,xp,beta,yp,info,side=side,d=diag,trans=trans) call psb_cssm(alpha,a,xp,beta,yp,info,scale=scale,d=diag,trans=trans)
if(info /= 0) then if(info /= 0) then
info = 4010 info = 4010
@ -354,14 +354,14 @@ end subroutine psb_dspsm
! desc_a - type(psb_desc_type). The communication descriptor. ! desc_a - type(psb_desc_type). The communication descriptor.
! info - integer. Return code ! info - integer. Return code
! trans - character(optional). Whether A or A'. If not present 'N' is assumed. ! trans - character(optional). Whether A or A'. If not present 'N' is assumed.
! side - character(optional). Specify some type of operation with ! scale - character(optional). Specify some type of operation with
! the diagonal matrix D. ! the diagonal matrix D.
! choice - integer(optional). The kind of update to perform on overlap elements. ! choice - integer(optional). The kind of update to perform on overlap elements.
! d(:) - real , optional Matrix for diagonal scaling. ! d(:) - real , optional Matrix for diagonal scaling.
! work(:) - real , optional Working area. ! work(:) - real , optional Working area.
! !
subroutine psb_dspsv(alpha,a,x,beta,y,desc_a,info,& subroutine psb_dspsv(alpha,a,x,beta,y,desc_a,info,&
& trans, side, choice, diag, work) & trans, scale, choice, diag, work)
use psb_descriptor_type use psb_descriptor_type
use psb_comm_mod use psb_comm_mod
use psi_mod use psi_mod
@ -380,7 +380,7 @@ subroutine psb_dspsv(alpha,a,x,beta,y,desc_a,info,&
integer, intent(out) :: info integer, intent(out) :: info
real(psb_dpk_), intent(in), optional, target :: diag(:) real(psb_dpk_), intent(in), optional, target :: diag(:)
real(psb_dpk_), optional, target :: work(:) real(psb_dpk_), optional, target :: work(:)
character, intent(in), optional :: trans, side character, intent(in), optional :: trans, scale
integer, intent(in), optional :: choice integer, intent(in), optional :: choice
! locals ! locals
@ -389,7 +389,7 @@ subroutine psb_dspsv(alpha,a,x,beta,y,desc_a,info,&
& ix, iy, ik, jx, jy, i, lld,& & ix, iy, ik, jx, jy, i, lld,&
& m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm & m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm
character :: lside character :: lscale
integer, parameter :: nb=4 integer, parameter :: nb=4
real(psb_dpk_),pointer :: iwork(:), xp(:), yp(:), id(:) real(psb_dpk_),pointer :: iwork(:), xp(:), yp(:), id(:)
character :: itrans character :: itrans
@ -425,10 +425,10 @@ subroutine psb_dspsv(alpha,a,x,beta,y,desc_a,info,&
choice_ = psb_avg_ choice_ = psb_avg_
endif endif
if (present(side)) then if (present(scale)) then
lside = psb_toupper(side) lscale = psb_toupper(scale)
else else
lside = 'U' lscale = 'U'
endif endif
if (present(trans)) then if (present(trans)) then
@ -525,7 +525,7 @@ subroutine psb_dspsv(alpha,a,x,beta,y,desc_a,info,&
! Perform local triangular system solve ! Perform local triangular system solve
xp => x(iix:lldx) xp => x(iix:lldx)
yp => y(iiy:lldy) yp => y(iiy:lldy)
call psb_cssm(alpha,a,xp,beta,yp,info,side=side,d=diag,trans=trans) call psb_cssm(alpha,a,xp,beta,yp,info,scale=scale,d=diag,trans=trans)
if(info /= 0) then if(info /= 0) then
info = 4010 info = 4010

@ -75,7 +75,7 @@
! !
! !
subroutine psb_sspsm(alpha,a,x,beta,y,desc_a,info,& subroutine psb_sspsm(alpha,a,x,beta,y,desc_a,info,&
& trans, side, choice, diag, k, jx, jy, work) & trans, scale, choice, diag, k, jx, jy, work)
use psb_descriptor_type use psb_descriptor_type
use psb_comm_mod use psb_comm_mod
@ -95,7 +95,7 @@ subroutine psb_sspsm(alpha,a,x,beta,y,desc_a,info,&
integer, intent(out) :: info integer, intent(out) :: info
real(psb_spk_), intent(in), optional, target :: diag(:) real(psb_spk_), intent(in), optional, target :: diag(:)
real(psb_spk_), optional, target :: work(:) real(psb_spk_), optional, target :: work(:)
character, intent(in), optional :: trans, side character, intent(in), optional :: trans, scale
integer, intent(in), optional :: choice integer, intent(in), optional :: choice
integer, intent(in), optional :: k, jx, jy integer, intent(in), optional :: k, jx, jy
@ -105,7 +105,7 @@ subroutine psb_sspsm(alpha,a,x,beta,y,desc_a,info,&
& ix, iy, ik, ijx, ijy, i, lld,& & ix, iy, ik, ijx, ijy, i, lld,&
& m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm & m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm
character :: lside character :: lscale
integer, parameter :: nb=4 integer, parameter :: nb=4
real(psb_spk_),pointer :: iwork(:), xp(:,:), yp(:,:), id(:) real(psb_spk_),pointer :: iwork(:), xp(:,:), yp(:,:), id(:)
character :: itrans character :: itrans
@ -157,10 +157,10 @@ subroutine psb_sspsm(alpha,a,x,beta,y,desc_a,info,&
choice_ = psb_avg_ choice_ = psb_avg_
endif endif
if (present(side)) then if (present(scale)) then
lside = psb_toupper(side) lscale = psb_toupper(scale)
else else
lside = 'U' lscale = 'U'
endif endif
if (present(trans)) then if (present(trans)) then
@ -256,7 +256,7 @@ subroutine psb_sspsm(alpha,a,x,beta,y,desc_a,info,&
! Perform local triangular system solve ! Perform local triangular system solve
xp => x(iix:lldx,jjx:jjx+ik-1) xp => x(iix:lldx,jjx:jjx+ik-1)
yp => y(iiy:lldy,jjy:jjy+ik-1) yp => y(iiy:lldy,jjy:jjy+ik-1)
call psb_cssm(alpha,a,xp,beta,yp,info,side=side,d=diag,trans=trans) call psb_cssm(alpha,a,xp,beta,yp,info,scale=scale,d=diag,trans=trans)
if(info /= 0) then if(info /= 0) then
info = 4010 info = 4010
@ -354,14 +354,14 @@ end subroutine psb_sspsm
! desc_a - type(psb_desc_type). The communication descriptor. ! desc_a - type(psb_desc_type). The communication descriptor.
! info - integer. Return code ! info - integer. Return code
! trans - character(optional). Whether A or A'. If not present 'N' is assumed. ! trans - character(optional). Whether A or A'. If not present 'N' is assumed.
! side - character(optional). Specify some type of operation with ! scale - character(optional). Specify some type of operation with
! the diagonal matrix D. ! the diagonal matrix D.
! choice - integer(optional). The kind of update to perform on overlap elements. ! choice - integer(optional). The kind of update to perform on overlap elements.
! d(:) - real , optional Matrix for diagonal scaling. ! d(:) - real , optional Matrix for diagonal scaling.
! work(:) - real , optional Working area. ! work(:) - real , optional Working area.
! !
subroutine psb_sspsv(alpha,a,x,beta,y,desc_a,info,& subroutine psb_sspsv(alpha,a,x,beta,y,desc_a,info,&
& trans, side, choice, diag, work) & trans, scale, choice, diag, work)
use psb_descriptor_type use psb_descriptor_type
use psb_comm_mod use psb_comm_mod
use psi_mod use psi_mod
@ -380,7 +380,7 @@ subroutine psb_sspsv(alpha,a,x,beta,y,desc_a,info,&
integer, intent(out) :: info integer, intent(out) :: info
real(psb_spk_), intent(in), optional, target :: diag(:) real(psb_spk_), intent(in), optional, target :: diag(:)
real(psb_spk_), optional, target :: work(:) real(psb_spk_), optional, target :: work(:)
character, intent(in), optional :: trans, side character, intent(in), optional :: trans, scale
integer, intent(in), optional :: choice integer, intent(in), optional :: choice
! locals ! locals
@ -389,7 +389,7 @@ subroutine psb_sspsv(alpha,a,x,beta,y,desc_a,info,&
& ix, iy, ik, jx, jy, i, lld,& & ix, iy, ik, jx, jy, i, lld,&
& m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm & m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm
character :: lside character :: lscale
integer, parameter :: nb=4 integer, parameter :: nb=4
real(psb_spk_),pointer :: iwork(:), xp(:), yp(:), id(:) real(psb_spk_),pointer :: iwork(:), xp(:), yp(:), id(:)
character :: itrans character :: itrans
@ -425,10 +425,10 @@ subroutine psb_sspsv(alpha,a,x,beta,y,desc_a,info,&
choice_ = psb_avg_ choice_ = psb_avg_
endif endif
if (present(side)) then if (present(scale)) then
lside = psb_toupper(side) lscale = psb_toupper(scale)
else else
lside = 'U' lscale = 'U'
endif endif
if (present(trans)) then if (present(trans)) then
@ -525,7 +525,7 @@ subroutine psb_sspsv(alpha,a,x,beta,y,desc_a,info,&
! Perform local triangular system solve ! Perform local triangular system solve
xp => x(iix:lldx) xp => x(iix:lldx)
yp => y(iiy:lldy) yp => y(iiy:lldy)
call psb_cssm(alpha,a,xp,beta,yp,info,side=side,d=diag,trans=trans) call psb_cssm(alpha,a,xp,beta,yp,info,scale=scale,d=diag,trans=trans)
if(info /= 0) then if(info /= 0) then
info = 4010 info = 4010

@ -64,7 +64,7 @@
! desc_a - type(psb_desc_type). The communication descriptor. ! desc_a - type(psb_desc_type). The communication descriptor.
! info - integer. Return code ! info - integer. Return code
! trans - character(optional). Whether A or A'. If not present 'N' is assumed. ! trans - character(optional). Whether A or A'. If not present 'N' is assumed.
! unitd - character(optional). Specify some type of operation with ! scale - character(optional). Specify some type of operation with
! the diagonal matrix D. ! the diagonal matrix D.
! choice - integer(optional). The kind of update to perform on overlap elements. ! choice - integer(optional). The kind of update to perform on overlap elements.
! d(:) - complex, optional Matrix for diagonal scaling. ! d(:) - complex, optional Matrix for diagonal scaling.
@ -74,7 +74,7 @@
! work(:) - complex, optional Working area. ! work(:) - complex, optional Working area.
! !
subroutine psb_zspsm(alpha,a,x,beta,y,desc_a,info,& subroutine psb_zspsm(alpha,a,x,beta,y,desc_a,info,&
& trans, side, choice, diag, k, jx, jy, work) & trans, scale, choice, diag, k, jx, jy, work)
use psb_descriptor_type use psb_descriptor_type
use psb_comm_mod use psb_comm_mod
@ -94,7 +94,7 @@ subroutine psb_zspsm(alpha,a,x,beta,y,desc_a,info,&
integer, intent(out) :: info integer, intent(out) :: info
complex(psb_dpk_), intent(in), optional, target :: diag(:) complex(psb_dpk_), intent(in), optional, target :: diag(:)
complex(psb_dpk_), optional, target :: work(:) complex(psb_dpk_), optional, target :: work(:)
character, intent(in), optional :: trans, side character, intent(in), optional :: trans, scale
integer, intent(in), optional :: choice integer, intent(in), optional :: choice
integer, intent(in), optional :: k, jx, jy integer, intent(in), optional :: k, jx, jy
@ -104,7 +104,7 @@ subroutine psb_zspsm(alpha,a,x,beta,y,desc_a,info,&
& ix, iy, ik, ijx, ijy, i, lld,& & ix, iy, ik, ijx, ijy, i, lld,&
& m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm & m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm
character :: lside character :: lscale
integer, parameter :: nb=4 integer, parameter :: nb=4
complex(psb_dpk_),pointer :: iwork(:), xp(:,:), yp(:,:), id(:) complex(psb_dpk_),pointer :: iwork(:), xp(:,:), yp(:,:), id(:)
character :: itrans character :: itrans
@ -156,10 +156,10 @@ subroutine psb_zspsm(alpha,a,x,beta,y,desc_a,info,&
choice_ = psb_avg_ choice_ = psb_avg_
endif endif
if (present(side)) then if (present(scale)) then
lside = psb_toupper(side) lscale = psb_toupper(scale)
else else
lside = 'U' lscale = 'U'
endif endif
if (present(trans)) then if (present(trans)) then
@ -255,7 +255,7 @@ subroutine psb_zspsm(alpha,a,x,beta,y,desc_a,info,&
! Perform local triangular system solve ! Perform local triangular system solve
xp => x(iix:lldx,jjx:jjx+ik-1) xp => x(iix:lldx,jjx:jjx+ik-1)
yp => y(iiy:lldy,jjy:jjy+ik-1) yp => y(iiy:lldy,jjy:jjy+ik-1)
call psb_cssm(alpha,a,xp,beta,yp,info,side=side,d=diag,trans=trans) call psb_cssm(alpha,a,xp,beta,yp,info,scale=scale,d=diag,trans=trans)
if(info /= 0) then if(info /= 0) then
info = 4010 info = 4010
@ -353,14 +353,14 @@ end subroutine psb_zspsm
! desc_a - type(psb_desc_type). The communication descriptor. ! desc_a - type(psb_desc_type). The communication descriptor.
! info - integer. Return code ! info - integer. Return code
! trans - character(optional). Whether A or A'. If not present 'N' is assumed. ! trans - character(optional). Whether A or A'. If not present 'N' is assumed.
! side - character(optional). Specify some type of operation with ! scale - character(optional). Specify some type of operation with
! the diagonal matrix D. ! the diagonal matrix D.
! choice - integer(optional). The kind of update to perform on overlap elements. ! choice - integer(optional). The kind of update to perform on overlap elements.
! d(:) - complex, optional Matrix for diagonal scaling. ! d(:) - complex, optional Matrix for diagonal scaling.
! work(:) - complex, optional Working area. ! work(:) - complex, optional Working area.
! !
subroutine psb_zspsv(alpha,a,x,beta,y,desc_a,info,& subroutine psb_zspsv(alpha,a,x,beta,y,desc_a,info,&
& trans, side, choice, diag, work) & trans, scale, choice, diag, work)
use psb_descriptor_type use psb_descriptor_type
use psb_comm_mod use psb_comm_mod
use psi_mod use psi_mod
@ -379,7 +379,7 @@ subroutine psb_zspsv(alpha,a,x,beta,y,desc_a,info,&
integer, intent(out) :: info integer, intent(out) :: info
complex(psb_dpk_), intent(in), optional, target :: diag(:) complex(psb_dpk_), intent(in), optional, target :: diag(:)
complex(psb_dpk_), optional, target :: work(:) complex(psb_dpk_), optional, target :: work(:)
character, intent(in), optional :: trans, side character, intent(in), optional :: trans, scale
integer, intent(in), optional :: choice integer, intent(in), optional :: choice
! locals ! locals
@ -388,7 +388,7 @@ subroutine psb_zspsv(alpha,a,x,beta,y,desc_a,info,&
& ix, iy, ik, jx, jy, i, lld,& & ix, iy, ik, jx, jy, i, lld,&
& m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm & m, nrow, ncol, liwork, llwork, iiy, jjy, idx, ndm
character :: lside character :: lscale
integer, parameter :: nb=4 integer, parameter :: nb=4
complex(psb_dpk_),pointer :: iwork(:), xp(:), yp(:), id(:) complex(psb_dpk_),pointer :: iwork(:), xp(:), yp(:), id(:)
character :: itrans character :: itrans
@ -424,10 +424,10 @@ subroutine psb_zspsv(alpha,a,x,beta,y,desc_a,info,&
choice_ = psb_avg_ choice_ = psb_avg_
endif endif
if (present(side)) then if (present(scale)) then
lside = psb_toupper(side) lscale = psb_toupper(scale)
else else
lside = 'U' lscale = 'U'
endif endif
if (present(trans)) then if (present(trans)) then
@ -524,7 +524,7 @@ subroutine psb_zspsv(alpha,a,x,beta,y,desc_a,info,&
! Perform local triangular system solve ! Perform local triangular system solve
xp => x(iix:lldx) xp => x(iix:lldx)
yp => y(iiy:lldy) yp => y(iiy:lldy)
call psb_cssm(alpha,a,xp,beta,yp,info,side=side,d=diag,trans=trans) call psb_cssm(alpha,a,xp,beta,yp,info,scale=scale,d=diag,trans=trans)
if(info /= 0) then if(info /= 0) then
info = 4010 info = 4010

@ -108,26 +108,26 @@ subroutine psb_cbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
case('N') case('N')
call psb_spsm(cone,prec%av(psb_l_pr_),x,czero,ww,desc_data,info,& call psb_spsm(cone,prec%av(psb_l_pr_),x,czero,ww,desc_data,info,&
& trans=trans_,side='L',diag=prec%d,choice=psb_none_,work=aux) & trans=trans_,scale='L',diag=prec%d,choice=psb_none_,work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
call psb_spsm(alpha,prec%av(psb_u_pr_),ww,beta,y,desc_data,info,& call psb_spsm(alpha,prec%av(psb_u_pr_),ww,beta,y,desc_data,info,&
& trans=trans_,side='U',choice=psb_none_, work=aux) & trans=trans_,scale='U',choice=psb_none_, work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
case('T') case('T')
call psb_spsm(cone,prec%av(psb_u_pr_),x,czero,ww,desc_data,info,& call psb_spsm(cone,prec%av(psb_u_pr_),x,czero,ww,desc_data,info,&
& trans=trans_,side='L',diag=prec%d,choice=psb_none_, work=aux) & trans=trans_,scale='L',diag=prec%d,choice=psb_none_, work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
call psb_spsm(alpha,prec%av(psb_l_pr_),ww,beta,y,desc_data,info,& call psb_spsm(alpha,prec%av(psb_l_pr_),ww,beta,y,desc_data,info,&
& trans=trans_,side='U',choice=psb_none_,work=aux) & trans=trans_,scale='U',choice=psb_none_,work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
case('C') case('C')
call psb_spsm(cone,prec%av(psb_u_pr_),x,czero,ww,desc_data,info,& call psb_spsm(cone,prec%av(psb_u_pr_),x,czero,ww,desc_data,info,&
& trans=trans_,side='L',diag=conjg(prec%d),choice=psb_none_, work=aux) & trans=trans_,scale='L',diag=conjg(prec%d),choice=psb_none_, work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
call psb_spsm(alpha,prec%av(psb_l_pr_),ww,beta,y,desc_data,info,& call psb_spsm(alpha,prec%av(psb_l_pr_),ww,beta,y,desc_data,info,&
& trans=trans_,side='U',choice=psb_none_,work=aux) & trans=trans_,scale='U',choice=psb_none_,work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
end select end select

@ -108,18 +108,18 @@ subroutine psb_dbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
case('N') case('N')
call psb_spsm(done,prec%av(psb_l_pr_),x,dzero,ww,desc_data,info,& call psb_spsm(done,prec%av(psb_l_pr_),x,dzero,ww,desc_data,info,&
& trans=trans_,side='L',diag=prec%d,choice=psb_none_,work=aux) & trans=trans_,scale='L',diag=prec%d,choice=psb_none_,work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
call psb_spsm(alpha,prec%av(psb_u_pr_),ww,beta,y,desc_data,info,& call psb_spsm(alpha,prec%av(psb_u_pr_),ww,beta,y,desc_data,info,&
& trans=trans_,side='U',choice=psb_none_, work=aux) & trans=trans_,scale='U',choice=psb_none_, work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
case('T','C') case('T','C')
call psb_spsm(done,prec%av(psb_u_pr_),x,dzero,ww,desc_data,info,& call psb_spsm(done,prec%av(psb_u_pr_),x,dzero,ww,desc_data,info,&
& trans=trans_,side='L',diag=prec%d,choice=psb_none_, work=aux) & trans=trans_,scale='L',diag=prec%d,choice=psb_none_, work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
call psb_spsm(alpha,prec%av(psb_l_pr_),ww,beta,y,desc_data,info,& call psb_spsm(alpha,prec%av(psb_l_pr_),ww,beta,y,desc_data,info,&
& trans=trans_,side='U',choice=psb_none_,work=aux) & trans=trans_,scale='U',choice=psb_none_,work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
end select end select

@ -108,18 +108,18 @@ subroutine psb_sbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
case('N') case('N')
call psb_spsm(sone,prec%av(psb_l_pr_),x,szero,ww,desc_data,info,& call psb_spsm(sone,prec%av(psb_l_pr_),x,szero,ww,desc_data,info,&
& trans=trans_,side='L',diag=prec%d,choice=psb_none_,work=aux) & trans=trans_,scale='L',diag=prec%d,choice=psb_none_,work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
call psb_spsm(alpha,prec%av(psb_u_pr_),ww,beta,y,desc_data,info,& call psb_spsm(alpha,prec%av(psb_u_pr_),ww,beta,y,desc_data,info,&
& trans=trans_,side='U',choice=psb_none_, work=aux) & trans=trans_,scale='U',choice=psb_none_, work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
case('T','C') case('T','C')
call psb_spsm(sone,prec%av(psb_u_pr_),x,szero,ww,desc_data,info,& call psb_spsm(sone,prec%av(psb_u_pr_),x,szero,ww,desc_data,info,&
& trans=trans_,side='L',diag=prec%d,choice=psb_none_, work=aux) & trans=trans_,scale='L',diag=prec%d,choice=psb_none_, work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
call psb_spsm(alpha,prec%av(psb_l_pr_),ww,beta,y,desc_data,info,& call psb_spsm(alpha,prec%av(psb_l_pr_),ww,beta,y,desc_data,info,&
& trans=trans_,side='U',choice=psb_none_,work=aux) & trans=trans_,scale='U',choice=psb_none_,work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
end select end select

@ -108,26 +108,26 @@ subroutine psb_zbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
case('N') case('N')
call psb_spsm(zone,prec%av(psb_l_pr_),x,zzero,ww,desc_data,info,& call psb_spsm(zone,prec%av(psb_l_pr_),x,zzero,ww,desc_data,info,&
& trans=trans_,side='L',diag=prec%d,choice=psb_none_,work=aux) & trans=trans_,scale='L',diag=prec%d,choice=psb_none_,work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
call psb_spsm(alpha,prec%av(psb_u_pr_),ww,beta,y,desc_data,info,& call psb_spsm(alpha,prec%av(psb_u_pr_),ww,beta,y,desc_data,info,&
& trans=trans_,side='U',choice=psb_none_, work=aux) & trans=trans_,scale='U',choice=psb_none_, work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
case('T') case('T')
call psb_spsm(zone,prec%av(psb_u_pr_),x,zzero,ww,desc_data,info,& call psb_spsm(zone,prec%av(psb_u_pr_),x,zzero,ww,desc_data,info,&
& trans=trans_,side='L',diag=prec%d,choice=psb_none_, work=aux) & trans=trans_,scale='L',diag=prec%d,choice=psb_none_, work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
call psb_spsm(alpha,prec%av(psb_l_pr_),ww,beta,y,desc_data,info,& call psb_spsm(alpha,prec%av(psb_l_pr_),ww,beta,y,desc_data,info,&
& trans=trans_,side='U',choice=psb_none_,work=aux) & trans=trans_,scale='U',choice=psb_none_,work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
case('C') case('C')
call psb_spsm(zone,prec%av(psb_u_pr_),x,zzero,ww,desc_data,info,& call psb_spsm(zone,prec%av(psb_u_pr_),x,zzero,ww,desc_data,info,&
& trans=trans_,side='L',diag=conjg(prec%d),choice=psb_none_, work=aux) & trans=trans_,scale='L',diag=conjg(prec%d),choice=psb_none_, work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
call psb_spsm(alpha,prec%av(psb_l_pr_),ww,beta,y,desc_data,info,& call psb_spsm(alpha,prec%av(psb_l_pr_),ww,beta,y,desc_data,info,&
& trans=trans_,side='U',choice=psb_none_,work=aux) & trans=trans_,scale='U',choice=psb_none_,work=aux)
if(info /=0) goto 9999 if(info /=0) goto 9999
end select end select

Loading…
Cancel
Save