New variant of psb_spins in CSR mode. Document same.

merge-paraggr
Salvatore Filippone 6 years ago
parent 883c026367
commit 242b9ec91f

@ -260,6 +260,28 @@ Module psb_c_tools_mod
logical, intent(in), optional :: rebuild
logical, intent(in), optional :: local
end subroutine psb_cspins
subroutine psb_cspins_csr_lirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
import
implicit none
type(psb_desc_type), intent(inout) :: desc_a
type(psb_cspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr
integer(psb_lpk_), intent(in) :: irw,irp(:),ja(:)
complex(psb_spk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
end subroutine psb_cspins_csr_lirp
subroutine psb_cspins_csr_iirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
import
implicit none
type(psb_desc_type), intent(inout) :: desc_a
type(psb_cspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr,irp(:)
integer(psb_lpk_), intent(in) :: irw,ja(:)
complex(psb_spk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
end subroutine psb_cspins_csr_iirp
subroutine psb_cspins_v(nz,ia,ja,val,a,desc_a,info,rebuild,local)
use psb_i_vect_mod, only : psb_i_vect_type
import

@ -260,6 +260,28 @@ Module psb_d_tools_mod
logical, intent(in), optional :: rebuild
logical, intent(in), optional :: local
end subroutine psb_dspins
subroutine psb_dspins_csr_lirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
import
implicit none
type(psb_desc_type), intent(inout) :: desc_a
type(psb_dspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr
integer(psb_lpk_), intent(in) :: irw,irp(:),ja(:)
real(psb_dpk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
end subroutine psb_dspins_csr_lirp
subroutine psb_dspins_csr_iirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
import
implicit none
type(psb_desc_type), intent(inout) :: desc_a
type(psb_dspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr,irp(:)
integer(psb_lpk_), intent(in) :: irw,ja(:)
real(psb_dpk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
end subroutine psb_dspins_csr_iirp
subroutine psb_dspins_v(nz,ia,ja,val,a,desc_a,info,rebuild,local)
use psb_i_vect_mod, only : psb_i_vect_type
import

@ -260,6 +260,28 @@ Module psb_s_tools_mod
logical, intent(in), optional :: rebuild
logical, intent(in), optional :: local
end subroutine psb_sspins
subroutine psb_sspins_csr_lirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
import
implicit none
type(psb_desc_type), intent(inout) :: desc_a
type(psb_sspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr
integer(psb_lpk_), intent(in) :: irw,irp(:),ja(:)
real(psb_spk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
end subroutine psb_sspins_csr_lirp
subroutine psb_sspins_csr_iirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
import
implicit none
type(psb_desc_type), intent(inout) :: desc_a
type(psb_sspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr,irp(:)
integer(psb_lpk_), intent(in) :: irw,ja(:)
real(psb_spk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
end subroutine psb_sspins_csr_iirp
subroutine psb_sspins_v(nz,ia,ja,val,a,desc_a,info,rebuild,local)
use psb_i_vect_mod, only : psb_i_vect_type
import

@ -260,6 +260,28 @@ Module psb_z_tools_mod
logical, intent(in), optional :: rebuild
logical, intent(in), optional :: local
end subroutine psb_zspins
subroutine psb_zspins_csr_lirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
import
implicit none
type(psb_desc_type), intent(inout) :: desc_a
type(psb_zspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr
integer(psb_lpk_), intent(in) :: irw,irp(:),ja(:)
complex(psb_dpk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
end subroutine psb_zspins_csr_lirp
subroutine psb_zspins_csr_iirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
import
implicit none
type(psb_desc_type), intent(inout) :: desc_a
type(psb_zspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr,irp(:)
integer(psb_lpk_), intent(in) :: irw,ja(:)
complex(psb_dpk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
end subroutine psb_zspins_csr_iirp
subroutine psb_zspins_v(nz,ia,ja,val,a,desc_a,info,rebuild,local)
use psb_i_vect_mod, only : psb_i_vect_type
import

@ -191,6 +191,199 @@ subroutine psb_cspins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
end subroutine psb_cspins
subroutine psb_cspins_csr_lirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
use psb_base_mod, psb_protect_name => psb_cspins_csr_lirp
use psi_mod
implicit none
!....parameters...
type(psb_desc_type), intent(inout) :: desc_a
type(psb_cspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr
integer(psb_lpk_), intent(in) :: irw,irp(:),ja(:)
complex(psb_spk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
!locals.....
integer(psb_ipk_) :: nrow, err_act, ncol, spstate, nz, i, j
integer(psb_lpk_) :: ir
integer(psb_ipk_) :: ictxt,np,me
logical, parameter :: debug=.false.
integer(psb_ipk_), parameter :: relocsz=200
logical :: rebuild_, local_
integer(psb_lpk_), allocatable :: ia(:)
character(len=20) :: name
info = psb_success_
name = 'psb_cspins_csr'
call psb_erractionsave(err_act)
ictxt = desc_a%get_context()
call psb_info(ictxt, me, np)
if (nr < 0) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(irp) < nr+1) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
nz = irp(nr+1) - 1
if (size(ja) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(val) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if ((nr == 0).or.(nz == 0)) return
if (present(rebuild)) then
rebuild_ = rebuild
else
rebuild_ = .false.
endif
if (present(local)) then
local_ = local
else
local_ = .false.
endif
allocate(ia(nz),stat=info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='allocate',i_err=(/info/))
goto 9999
end if
do i = 1, nr
ir = i-1+irw
do j=irp(i),irp(i+1)-1
ia(j) = ir
end do
end do
call psb_spins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='spins_coo',i_err=(/info/))
goto 9999
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_cspins_csr_lirp
subroutine psb_cspins_csr_iirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
use psb_base_mod, psb_protect_name => psb_cspins_csr_iirp
use psi_mod
implicit none
!....parameters...
type(psb_desc_type), intent(inout) :: desc_a
type(psb_cspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr,irp(:)
integer(psb_lpk_), intent(in) :: irw,ja(:)
complex(psb_spk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
!locals.....
integer(psb_ipk_) :: nrow, err_act, ncol, spstate, nz, i, j
integer(psb_lpk_) :: ir
integer(psb_ipk_) :: ictxt,np,me
logical, parameter :: debug=.false.
integer(psb_ipk_), parameter :: relocsz=200
logical :: rebuild_, local_
integer(psb_lpk_), allocatable :: ia(:)
character(len=20) :: name
info = psb_success_
name = 'psb_cspins_csr'
call psb_erractionsave(err_act)
ictxt = desc_a%get_context()
call psb_info(ictxt, me, np)
if (nr < 0) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(irp) < nr+1) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
nz = irp(nr+1) - 1
if (size(ja) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(val) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if ((nr == 0).or.(nz == 0)) return
if (present(rebuild)) then
rebuild_ = rebuild
else
rebuild_ = .false.
endif
if (present(local)) then
local_ = local
else
local_ = .false.
endif
allocate(ia(nz),stat=info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='allocate',i_err=(/info/))
goto 9999
end if
do i = 1, nr
ir = i-1+irw
do j=irp(i),irp(i+1)-1
ia(j) = ir
end do
end do
call psb_spins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='spins_coo',i_err=(/info/))
goto 9999
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_cspins_csr_iirp
subroutine psb_cspins_2desc(nz,ia,ja,val,a,desc_ar,desc_ac,info)
use psb_base_mod, psb_protect_name => psb_cspins_2desc

@ -191,6 +191,199 @@ subroutine psb_dspins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
end subroutine psb_dspins
subroutine psb_dspins_csr_lirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
use psb_base_mod, psb_protect_name => psb_dspins_csr_lirp
use psi_mod
implicit none
!....parameters...
type(psb_desc_type), intent(inout) :: desc_a
type(psb_dspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr
integer(psb_lpk_), intent(in) :: irw,irp(:),ja(:)
real(psb_dpk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
!locals.....
integer(psb_ipk_) :: nrow, err_act, ncol, spstate, nz, i, j
integer(psb_lpk_) :: ir
integer(psb_ipk_) :: ictxt,np,me
logical, parameter :: debug=.false.
integer(psb_ipk_), parameter :: relocsz=200
logical :: rebuild_, local_
integer(psb_lpk_), allocatable :: ia(:)
character(len=20) :: name
info = psb_success_
name = 'psb_dspins_csr'
call psb_erractionsave(err_act)
ictxt = desc_a%get_context()
call psb_info(ictxt, me, np)
if (nr < 0) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(irp) < nr+1) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
nz = irp(nr+1) - 1
if (size(ja) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(val) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if ((nr == 0).or.(nz == 0)) return
if (present(rebuild)) then
rebuild_ = rebuild
else
rebuild_ = .false.
endif
if (present(local)) then
local_ = local
else
local_ = .false.
endif
allocate(ia(nz),stat=info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='allocate',i_err=(/info/))
goto 9999
end if
do i = 1, nr
ir = i-1+irw
do j=irp(i),irp(i+1)-1
ia(j) = ir
end do
end do
call psb_spins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='spins_coo',i_err=(/info/))
goto 9999
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_dspins_csr_lirp
subroutine psb_dspins_csr_iirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
use psb_base_mod, psb_protect_name => psb_dspins_csr_iirp
use psi_mod
implicit none
!....parameters...
type(psb_desc_type), intent(inout) :: desc_a
type(psb_dspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr,irp(:)
integer(psb_lpk_), intent(in) :: irw,ja(:)
real(psb_dpk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
!locals.....
integer(psb_ipk_) :: nrow, err_act, ncol, spstate, nz, i, j
integer(psb_lpk_) :: ir
integer(psb_ipk_) :: ictxt,np,me
logical, parameter :: debug=.false.
integer(psb_ipk_), parameter :: relocsz=200
logical :: rebuild_, local_
integer(psb_lpk_), allocatable :: ia(:)
character(len=20) :: name
info = psb_success_
name = 'psb_dspins_csr'
call psb_erractionsave(err_act)
ictxt = desc_a%get_context()
call psb_info(ictxt, me, np)
if (nr < 0) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(irp) < nr+1) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
nz = irp(nr+1) - 1
if (size(ja) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(val) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if ((nr == 0).or.(nz == 0)) return
if (present(rebuild)) then
rebuild_ = rebuild
else
rebuild_ = .false.
endif
if (present(local)) then
local_ = local
else
local_ = .false.
endif
allocate(ia(nz),stat=info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='allocate',i_err=(/info/))
goto 9999
end if
do i = 1, nr
ir = i-1+irw
do j=irp(i),irp(i+1)-1
ia(j) = ir
end do
end do
call psb_spins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='spins_coo',i_err=(/info/))
goto 9999
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_dspins_csr_iirp
subroutine psb_dspins_2desc(nz,ia,ja,val,a,desc_ar,desc_ac,info)
use psb_base_mod, psb_protect_name => psb_dspins_2desc

@ -191,6 +191,199 @@ subroutine psb_sspins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
end subroutine psb_sspins
subroutine psb_sspins_csr_lirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
use psb_base_mod, psb_protect_name => psb_sspins_csr_lirp
use psi_mod
implicit none
!....parameters...
type(psb_desc_type), intent(inout) :: desc_a
type(psb_sspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr
integer(psb_lpk_), intent(in) :: irw,irp(:),ja(:)
real(psb_spk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
!locals.....
integer(psb_ipk_) :: nrow, err_act, ncol, spstate, nz, i, j
integer(psb_lpk_) :: ir
integer(psb_ipk_) :: ictxt,np,me
logical, parameter :: debug=.false.
integer(psb_ipk_), parameter :: relocsz=200
logical :: rebuild_, local_
integer(psb_lpk_), allocatable :: ia(:)
character(len=20) :: name
info = psb_success_
name = 'psb_sspins_csr'
call psb_erractionsave(err_act)
ictxt = desc_a%get_context()
call psb_info(ictxt, me, np)
if (nr < 0) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(irp) < nr+1) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
nz = irp(nr+1) - 1
if (size(ja) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(val) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if ((nr == 0).or.(nz == 0)) return
if (present(rebuild)) then
rebuild_ = rebuild
else
rebuild_ = .false.
endif
if (present(local)) then
local_ = local
else
local_ = .false.
endif
allocate(ia(nz),stat=info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='allocate',i_err=(/info/))
goto 9999
end if
do i = 1, nr
ir = i-1+irw
do j=irp(i),irp(i+1)-1
ia(j) = ir
end do
end do
call psb_spins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='spins_coo',i_err=(/info/))
goto 9999
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_sspins_csr_lirp
subroutine psb_sspins_csr_iirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
use psb_base_mod, psb_protect_name => psb_sspins_csr_iirp
use psi_mod
implicit none
!....parameters...
type(psb_desc_type), intent(inout) :: desc_a
type(psb_sspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr,irp(:)
integer(psb_lpk_), intent(in) :: irw,ja(:)
real(psb_spk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
!locals.....
integer(psb_ipk_) :: nrow, err_act, ncol, spstate, nz, i, j
integer(psb_lpk_) :: ir
integer(psb_ipk_) :: ictxt,np,me
logical, parameter :: debug=.false.
integer(psb_ipk_), parameter :: relocsz=200
logical :: rebuild_, local_
integer(psb_lpk_), allocatable :: ia(:)
character(len=20) :: name
info = psb_success_
name = 'psb_sspins_csr'
call psb_erractionsave(err_act)
ictxt = desc_a%get_context()
call psb_info(ictxt, me, np)
if (nr < 0) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(irp) < nr+1) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
nz = irp(nr+1) - 1
if (size(ja) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(val) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if ((nr == 0).or.(nz == 0)) return
if (present(rebuild)) then
rebuild_ = rebuild
else
rebuild_ = .false.
endif
if (present(local)) then
local_ = local
else
local_ = .false.
endif
allocate(ia(nz),stat=info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='allocate',i_err=(/info/))
goto 9999
end if
do i = 1, nr
ir = i-1+irw
do j=irp(i),irp(i+1)-1
ia(j) = ir
end do
end do
call psb_spins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='spins_coo',i_err=(/info/))
goto 9999
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_sspins_csr_iirp
subroutine psb_sspins_2desc(nz,ia,ja,val,a,desc_ar,desc_ac,info)
use psb_base_mod, psb_protect_name => psb_sspins_2desc

@ -191,6 +191,199 @@ subroutine psb_zspins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
end subroutine psb_zspins
subroutine psb_zspins_csr_lirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
use psb_base_mod, psb_protect_name => psb_zspins_csr_lirp
use psi_mod
implicit none
!....parameters...
type(psb_desc_type), intent(inout) :: desc_a
type(psb_zspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr
integer(psb_lpk_), intent(in) :: irw,irp(:),ja(:)
complex(psb_dpk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
!locals.....
integer(psb_ipk_) :: nrow, err_act, ncol, spstate, nz, i, j
integer(psb_lpk_) :: ir
integer(psb_ipk_) :: ictxt,np,me
logical, parameter :: debug=.false.
integer(psb_ipk_), parameter :: relocsz=200
logical :: rebuild_, local_
integer(psb_lpk_), allocatable :: ia(:)
character(len=20) :: name
info = psb_success_
name = 'psb_zspins_csr'
call psb_erractionsave(err_act)
ictxt = desc_a%get_context()
call psb_info(ictxt, me, np)
if (nr < 0) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(irp) < nr+1) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
nz = irp(nr+1) - 1
if (size(ja) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(val) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if ((nr == 0).or.(nz == 0)) return
if (present(rebuild)) then
rebuild_ = rebuild
else
rebuild_ = .false.
endif
if (present(local)) then
local_ = local
else
local_ = .false.
endif
allocate(ia(nz),stat=info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='allocate',i_err=(/info/))
goto 9999
end if
do i = 1, nr
ir = i-1+irw
do j=irp(i),irp(i+1)-1
ia(j) = ir
end do
end do
call psb_spins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='spins_coo',i_err=(/info/))
goto 9999
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_zspins_csr_lirp
subroutine psb_zspins_csr_iirp(nr,irw,irp,ja,val,a,desc_a,info,rebuild,local)
use psb_base_mod, psb_protect_name => psb_zspins_csr_iirp
use psi_mod
implicit none
!....parameters...
type(psb_desc_type), intent(inout) :: desc_a
type(psb_zspmat_type), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nr,irp(:)
integer(psb_lpk_), intent(in) :: irw,ja(:)
complex(psb_dpk_), intent(in) :: val(:)
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: rebuild, local
!locals.....
integer(psb_ipk_) :: nrow, err_act, ncol, spstate, nz, i, j
integer(psb_lpk_) :: ir
integer(psb_ipk_) :: ictxt,np,me
logical, parameter :: debug=.false.
integer(psb_ipk_), parameter :: relocsz=200
logical :: rebuild_, local_
integer(psb_lpk_), allocatable :: ia(:)
character(len=20) :: name
info = psb_success_
name = 'psb_zspins_csr'
call psb_erractionsave(err_act)
ictxt = desc_a%get_context()
call psb_info(ictxt, me, np)
if (nr < 0) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(irp) < nr+1) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
nz = irp(nr+1) - 1
if (size(ja) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if (size(val) < nz) then
info = 1111
call psb_errpush(info,name)
goto 9999
end if
if ((nr == 0).or.(nz == 0)) return
if (present(rebuild)) then
rebuild_ = rebuild
else
rebuild_ = .false.
endif
if (present(local)) then
local_ = local
else
local_ = .false.
endif
allocate(ia(nz),stat=info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='allocate',i_err=(/info/))
goto 9999
end if
do i = 1, nr
ir = i-1+irw
do j=irp(i),irp(i+1)-1
ia(j) = ir
end do
end do
call psb_spins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_ai_,name,&
& a_err='spins_coo',i_err=(/info/))
goto 9999
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_zspins_csr_iirp
subroutine psb_zspins_2desc(nz,ia,ja,val,a,desc_ar,desc_ac,info)
use psb_base_mod, psb_protect_name => psb_zspins_2desc

@ -137,7 +137,7 @@ sample scatter/gather routines.
.
</PRE>
</DD>
<DT><A NAME="foot7826">... follows</A><A
<DT><A NAME="foot7863">... follows</A><A
HREF="node126.html#tex2html31"><SUP><SPAN CLASS="arabic">4</SPAN></SUP></A></DT>
<DD>The string is case-insensitive
@ -173,12 +173,12 @@ sample scatter/gather routines.
.
</PRE>
</DD>
<DT><A NAME="foot8281">... method</A><A
<DT><A NAME="foot8318">... method</A><A
HREF="node133.html#tex2html32"><SUP><SPAN CLASS="arabic">5</SPAN></SUP></A></DT>
<DD>Note:
the implementation is for <SPAN CLASS="MATH"><IMG
WIDTH="62" HEIGHT="32" ALIGN="MIDDLE" BORDER="0"
SRC="img169.png"
SRC="img174.png"
ALT="$FCG(1)$"></SPAN>.
<PRE>.

Binary file not shown.

Before

Width:  |  Height:  |  Size: 194 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 737 B

After

Width:  |  Height:  |  Size: 194 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 373 B

After

Width:  |  Height:  |  Size: 737 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 134 B

After

Width:  |  Height:  |  Size: 373 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 257 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 390 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 263 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 244 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 276 B

After

Width:  |  Height:  |  Size: 134 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 374 B

After

Width:  |  Height:  |  Size: 257 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 222 B

After

Width:  |  Height:  |  Size: 390 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 259 B

After

Width:  |  Height:  |  Size: 263 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 808 B

After

Width:  |  Height:  |  Size: 244 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 412 B

After

Width:  |  Height:  |  Size: 276 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 431 B

After

Width:  |  Height:  |  Size: 374 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 354 B

After

Width:  |  Height:  |  Size: 222 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 310 B

After

Width:  |  Height:  |  Size: 259 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 839 B

After

Width:  |  Height:  |  Size: 808 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 335 B

After

Width:  |  Height:  |  Size: 412 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 500 B

After

Width:  |  Height:  |  Size: 431 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 402 B

After

Width:  |  Height:  |  Size: 354 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 267 B

After

Width:  |  Height:  |  Size: 310 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 533 B

After

Width:  |  Height:  |  Size: 839 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 545 B

After

Width:  |  Height:  |  Size: 335 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 335 B

After

Width:  |  Height:  |  Size: 500 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 232 B

After

Width:  |  Height:  |  Size: 402 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 520 B

After

Width:  |  Height:  |  Size: 267 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 613 B

After

Width:  |  Height:  |  Size: 533 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 581 B

After

Width:  |  Height:  |  Size: 545 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 312 B

After

Width:  |  Height:  |  Size: 335 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 277 B

After

Width:  |  Height:  |  Size: 232 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 870 B

After

Width:  |  Height:  |  Size: 520 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 215 B

After

Width:  |  Height:  |  Size: 613 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 583 B

After

Width:  |  Height:  |  Size: 581 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 732 B

After

Width:  |  Height:  |  Size: 312 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 523 B

After

Width:  |  Height:  |  Size: 277 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 268 B

After

Width:  |  Height:  |  Size: 870 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 572 B

After

Width:  |  Height:  |  Size: 215 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 240 B

After

Width:  |  Height:  |  Size: 583 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 0 B

After

Width:  |  Height:  |  Size: 732 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 8.4 KiB

After

Width:  |  Height:  |  Size: 523 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 0 B

After

Width:  |  Height:  |  Size: 268 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 1.1 KiB

After

Width:  |  Height:  |  Size: 572 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 758 B

After

Width:  |  Height:  |  Size: 240 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 875 B

After

Width:  |  Height:  |  Size: 0 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 867 B

After

Width:  |  Height:  |  Size: 8.4 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 1.1 KiB

After

Width:  |  Height:  |  Size: 0 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 1.3 KiB

After

Width:  |  Height:  |  Size: 1.1 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 1.0 KiB

After

Width:  |  Height:  |  Size: 758 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 1.1 KiB

After

Width:  |  Height:  |  Size: 875 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 1.2 KiB

After

Width:  |  Height:  |  Size: 867 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 1.1 KiB

After

Width:  |  Height:  |  Size: 1.1 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 373 B

After

Width:  |  Height:  |  Size: 1.3 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 431 B

After

Width:  |  Height:  |  Size: 1.0 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 304 B

After

Width:  |  Height:  |  Size: 1.1 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 915 B

After

Width:  |  Height:  |  Size: 1.2 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 678 B

After

Width:  |  Height:  |  Size: 1.1 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 659 B

After

Width:  |  Height:  |  Size: 373 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 219 B

After

Width:  |  Height:  |  Size: 431 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 429 B

After

Width:  |  Height:  |  Size: 304 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 2.4 KiB

After

Width:  |  Height:  |  Size: 915 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 449 B

After

Width:  |  Height:  |  Size: 678 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 478 B

After

Width:  |  Height:  |  Size: 659 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 410 B

After

Width:  |  Height:  |  Size: 219 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 354 B

After

Width:  |  Height:  |  Size: 429 B

Binary file not shown.

Before

Width:  |  Height:  |  Size: 208 B

After

Width:  |  Height:  |  Size: 2.4 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 395 B

After

Width:  |  Height:  |  Size: 449 B

@ -251,7 +251,7 @@ of a dense vector</A>
<LI><A NAME="tex2html114"
HREF="node78.html">psb_spall -- Allocates a sparse matrix</A>
<LI><A NAME="tex2html115"
HREF="node79.html">psb_spins -- Insert a cloud of elements into a sparse
HREF="node79.html">psb_spins -- Insert a set of coefficients into a sparse
matrix</A>
<LI><A NAME="tex2html116"
HREF="node80.html">psb_spasb -- Sparse matrix assembly routine</A>

@ -139,7 +139,7 @@ Specified as: an integer variable.
</LI>
<LI>It is an error to specify a value for <SPAN CLASS="MATH"><IMG
WIDTH="22" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img129.png"
SRC="img134.png"
ALT="$np$"></SPAN> greater than the
number of processes available in the underlying base parallel
environment.

@ -101,7 +101,7 @@ Specified as: an integer value. <!-- MATH
-->
<SPAN CLASS="MATH"><IMG
WIDTH="139" HEIGHT="29" ALIGN="MIDDLE" BORDER="0"
SRC="img130.png"
SRC="img135.png"
ALT="$-1 \le iam \le np-1$"></SPAN> </DD>
<DT><STRONG>np</STRONG></DT>
<DD>Number of processes in the PSBLAS virtual parallel machine.
@ -125,14 +125,14 @@ Specified as: an integer variable. </DD>
-->
<SPAN CLASS="MATH"><IMG
WIDTH="128" HEIGHT="29" ALIGN="MIDDLE" BORDER="0"
SRC="img131.png"
SRC="img136.png"
ALT="$0 \le iam \le np-1$"></SPAN>;
</LI>
<LI>If the user has requested on <code>psb_init</code> a number of
processes less than the total available in the parallel execution
environment, the remaining processes will have on return <SPAN CLASS="MATH"><IMG
WIDTH="73" HEIGHT="29" ALIGN="MIDDLE" BORDER="0"
SRC="img132.png"
SRC="img137.png"
ALT="$iam=-1$"></SPAN>;
the only call involving <code>icontxt</code> that any such process may
execute is to <code>psb_exit</code>.

@ -101,7 +101,7 @@ Specified as: a logical variable, default value: true.
<LI>This routine may be called even if a previous call to
<code>psb_info</code> has returned with <SPAN CLASS="MATH"><IMG
WIDTH="73" HEIGHT="29" ALIGN="MIDDLE" BORDER="0"
SRC="img132.png"
SRC="img137.png"
ALT="$iam=-1$"></SPAN>; indeed, it it is the only
routine that may be called with argument <code>icontxt</code> in this
situation.

@ -60,7 +60,7 @@ call psb_get_rank(rank, icontxt, id)
<P>
This subroutine returns the MPI rank of the PSBLAS process <SPAN CLASS="MATH"><IMG
WIDTH="18" HEIGHT="14" ALIGN="BOTTOM" BORDER="0"
SRC="img133.png"
SRC="img138.png"
ALT="$id$"></SPAN>
<DL>
<DT><STRONG>Type:</STRONG></DT>
@ -95,7 +95,7 @@ Specified as: an integer value. <!-- MATH
-->
<SPAN CLASS="MATH"><IMG
WIDTH="113" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img134.png"
SRC="img139.png"
ALT="$0 \le id \le np-1$"></SPAN> </DD>
</DL>
@ -107,7 +107,7 @@ Specified as: an integer value. <!-- MATH
<DT><STRONG>rank</STRONG></DT>
<DD>The MPI rank associated with the PSBLAS process <SPAN CLASS="MATH"><IMG
WIDTH="18" HEIGHT="14" ALIGN="BOTTOM" BORDER="0"
SRC="img133.png"
SRC="img138.png"
ALT="$id$"></SPAN>.
<BR>
Scope: <B>local</B>.

@ -106,7 +106,7 @@ Specified as: an integer value <!-- MATH
-->
<SPAN CLASS="MATH"><IMG
WIDTH="153" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img135.png"
SRC="img140.png"
ALT="$0&lt;= root &lt;= np-1$"></SPAN>, default 0 </DD>
</DL>

@ -109,7 +109,7 @@ Specified as: an integer value <!-- MATH
-->
<SPAN CLASS="MATH"><IMG
WIDTH="165" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img136.png"
SRC="img141.png"
ALT="$-1&lt;= root &lt;= np-1$"></SPAN>, default -1. </DD>
</DL>

@ -109,7 +109,7 @@ Specified as: an integer value <!-- MATH
-->
<SPAN CLASS="MATH"><IMG
WIDTH="165" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img136.png"
SRC="img141.png"
ALT="$-1&lt;= root &lt;= np-1$"></SPAN>, default -1.
<BR></DD>
</DL>

@ -109,7 +109,7 @@ Specified as: an integer value <!-- MATH
-->
<SPAN CLASS="MATH"><IMG
WIDTH="165" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img136.png"
SRC="img141.png"
ALT="$-1&lt;= root &lt;= np-1$"></SPAN>, default -1.
<BR></DD>
</DL>

@ -109,7 +109,7 @@ Specified as: an integer value <!-- MATH
-->
<SPAN CLASS="MATH"><IMG
WIDTH="165" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img136.png"
SRC="img141.png"
ALT="$-1&lt;= root &lt;= np-1$"></SPAN>, default -1.
<BR></DD>
</DL>

@ -109,7 +109,7 @@ Specified as: an integer value <!-- MATH
-->
<SPAN CLASS="MATH"><IMG
WIDTH="165" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img136.png"
SRC="img141.png"
ALT="$-1&lt;= root &lt;= np-1$"></SPAN>, default -1.
<BR></DD>
</DL>

@ -109,7 +109,7 @@ Specified as: an integer value <!-- MATH
-->
<SPAN CLASS="MATH"><IMG
WIDTH="165" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img136.png"
SRC="img141.png"
ALT="$-1&lt;= root &lt;= np-1$"></SPAN>, default -1.
<BR></DD>
</DL>
@ -144,10 +144,10 @@ Kind, rank and size must agree on all processes.
</LI>
<LI>Denoting by <SPAN CLASS="MATH"><IMG
WIDTH="32" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img137.png"
SRC="img142.png"
ALT="$dat_i$"></SPAN> the value of the variable <SPAN CLASS="MATH"><IMG
WIDTH="26" HEIGHT="14" ALIGN="BOTTOM" BORDER="0"
SRC="img138.png"
SRC="img143.png"
ALT="$dat$"></SPAN> on process
<SPAN CLASS="MATH"><IMG
WIDTH="9" HEIGHT="17" ALIGN="BOTTOM" BORDER="0"
@ -166,7 +166,7 @@ res = \sqrt{\sum_i dat_i^2},
<IMG
WIDTH="119" HEIGHT="55" BORDER="0"
SRC="img139.png"
SRC="img144.png"
ALT="\begin{displaymath}res = \sqrt{\sum_i dat_i^2},\end{displaymath}">
</DIV>
<BR CLEAR="ALL">

@ -90,7 +90,7 @@ Intent: <B>in</B>.
Specified as: an integer, real or complex variable, which may be a
scalar, or a rank 1 or 2 array, or a character or logical scalar. Type, kind and rank must agree on sender and receiver process; if <SPAN CLASS="MATH"><IMG
WIDTH="18" HEIGHT="13" ALIGN="BOTTOM" BORDER="0"
SRC="img140.png"
SRC="img145.png"
ALT="$m$"></SPAN> is
not specified, size must agree as well.
</DD>
@ -108,7 +108,7 @@ Specified as: an integer value <!-- MATH
-->
<SPAN CLASS="MATH"><IMG
WIDTH="146" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img141.png"
SRC="img146.png"
ALT="$0&lt;= dst &lt;= np-1$"></SPAN>.
<BR></DD>
<DT><STRONG>m</STRONG></DT>
@ -125,16 +125,16 @@ Specified as: an integer value <!-- MATH
-->
<SPAN CLASS="MATH"><IMG
WIDTH="171" HEIGHT="32" ALIGN="MIDDLE" BORDER="0"
SRC="img142.png"
SRC="img147.png"
ALT="$0&lt;= m &lt;= size(dat,1)$"></SPAN>.
<BR>
When <SPAN CLASS="MATH"><IMG
WIDTH="26" HEIGHT="14" ALIGN="BOTTOM" BORDER="0"
SRC="img138.png"
SRC="img143.png"
ALT="$dat$"></SPAN> is a rank 2 array, specifies the number of rows to be sent
independently of the leading dimension <SPAN CLASS="MATH"><IMG
WIDTH="83" HEIGHT="32" ALIGN="MIDDLE" BORDER="0"
SRC="img143.png"
SRC="img148.png"
ALT="$size(dat,1)$"></SPAN>; must have the
same value on sending and receiving processes.
</DD>
@ -154,7 +154,7 @@ same value on sending and receiving processes.
<LI>This subroutine implies a synchronization, but only between the
calling process and the destination process <SPAN CLASS="MATH"><IMG
WIDTH="25" HEIGHT="14" ALIGN="BOTTOM" BORDER="0"
SRC="img144.png"
SRC="img149.png"
ALT="$dst$"></SPAN>.
</LI>
</OL>

@ -91,7 +91,7 @@ Specified as: an integer value <!-- MATH
-->
<SPAN CLASS="MATH"><IMG
WIDTH="147" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img145.png"
SRC="img150.png"
ALT="$0&lt;= src &lt;= np-1$"></SPAN>.
<BR></DD>
<DT><STRONG>m</STRONG></DT>
@ -108,16 +108,16 @@ Specified as: an integer value <!-- MATH
-->
<SPAN CLASS="MATH"><IMG
WIDTH="171" HEIGHT="32" ALIGN="MIDDLE" BORDER="0"
SRC="img142.png"
SRC="img147.png"
ALT="$0&lt;= m &lt;= size(dat,1)$"></SPAN>.
<BR>
When <SPAN CLASS="MATH"><IMG
WIDTH="26" HEIGHT="14" ALIGN="BOTTOM" BORDER="0"
SRC="img138.png"
SRC="img143.png"
ALT="$dat$"></SPAN> is a rank 2 array, specifies the number of rows to be sent
independently of the leading dimension <SPAN CLASS="MATH"><IMG
WIDTH="83" HEIGHT="32" ALIGN="MIDDLE" BORDER="0"
SRC="img143.png"
SRC="img148.png"
ALT="$size(dat,1)$"></SPAN>; must have the
same value on sending and receiving processes.
</DD>
@ -140,7 +140,7 @@ Intent: <B>inout</B>.
Specified as: an integer, real or complex variable, which may be a
scalar, or a rank 1 or 2 array, or a character or logical scalar. Type, kind and rank must agree on sender and receiver process; if <SPAN CLASS="MATH"><IMG
WIDTH="18" HEIGHT="13" ALIGN="BOTTOM" BORDER="0"
SRC="img140.png"
SRC="img145.png"
ALT="$m$"></SPAN> is
not specified, size must agree as well.
</DD>
@ -153,7 +153,7 @@ not specified, size must agree as well.
<LI>This subroutine implies a synchronization, but only between the
calling process and the source process <SPAN CLASS="MATH"><IMG
WIDTH="26" HEIGHT="13" ALIGN="BOTTOM" BORDER="0"
SRC="img146.png"
SRC="img151.png"
ALT="$src$"></SPAN>.
</LI>
</OL>

@ -91,7 +91,7 @@ explicitly.
<P>
<DIV ALIGN="CENTER"><A NAME="fig:routerr"></A><A NAME="7444"></A>
<DIV ALIGN="CENTER"><A NAME="fig:routerr"></A><A NAME="7481"></A>
<TABLE>
<CAPTION ALIGN="BOTTOM"><STRONG>Figure 9:</STRONG>
The layout of a generic <TT>psb_foo</TT>
@ -105,7 +105,7 @@ The layout of a generic <TT>psb_foo</TT>
-->
<SPAN CLASS="MATH"><IMG
WIDTH="562" HEIGHT="482" ALIGN="MIDDLE" BORDER="0"
SRC="img148.png"
SRC="img153.png"
ALT="\fbox{\TheSbox}"></SPAN>
</DIV></TD></TR>
</TABLE>
@ -121,7 +121,7 @@ called by <code>psb_spasb</code> ... by process 0 (i.e. the root process).
<P>
<DIV ALIGN="CENTER"><A NAME="fig:errormsg"></A><A NAME="7445"></A>
<DIV ALIGN="CENTER"><A NAME="fig:errormsg"></A><A NAME="7482"></A>
<TABLE>
<CAPTION ALIGN="BOTTOM"><STRONG>Figure 10:</STRONG>
A sample PSBLAS-2.0 error
@ -135,7 +135,7 @@ A sample PSBLAS-2.0 error
-->
<SPAN CLASS="MATH"><IMG
WIDTH="562" HEIGHT="482" ALIGN="MIDDLE" BORDER="0"
SRC="img148.png"
SRC="img153.png"
ALT="\fbox{\TheSbox}"></SPAN>
</DIV></TD></TR>
</TABLE>
@ -149,7 +149,7 @@ ifstarsubroutinesubroutinepsb_errpushPushes an error code onto the error
<BR>
<IMG
WIDTH="423" HEIGHT="16" ALIGN="BOTTOM" BORDER="0"
SRC="img150.png"
SRC="img155.png"
ALT="\begin{lstlisting}
call psb_errpush(err_c, r_name, i_err, a_err)
\end{lstlisting}">
@ -213,7 +213,7 @@ ifstarsubroutinesubroutinepsb_errorPrints the error stack content and aborts
<BR>
<IMG
WIDTH="213" HEIGHT="16" ALIGN="BOTTOM" BORDER="0"
SRC="img151.png"
SRC="img156.png"
ALT="\begin{lstlisting}
call psb_error(icontxt)
\end{lstlisting}">
@ -248,7 +248,7 @@ ifstarsubroutinesubroutinepsb_set_errverbositySets the verbosity of error
<BR>
<IMG
WIDTH="261" HEIGHT="16" ALIGN="BOTTOM" BORDER="0"
SRC="img152.png"
SRC="img157.png"
ALT="\begin{lstlisting}
call psb_set_errverbosity(v)
\end{lstlisting}">
@ -283,7 +283,7 @@ ifstarsubroutinesubroutinepsb_set_erractionSet the type of action to be
<BR>
<IMG
WIDTH="289" HEIGHT="16" ALIGN="BOTTOM" BORDER="0"
SRC="img153.png"
SRC="img158.png"
ALT="\begin{lstlisting}
call psb_set_erraction(err_act)
\end{lstlisting}">

@ -57,7 +57,7 @@
<BR>
<IMG
WIDTH="461" HEIGHT="16" ALIGN="BOTTOM" BORDER="0"
SRC="img154.png"
SRC="img159.png"
ALT="\begin{lstlisting}
call hb_read(a, iret, iunit, filename, b, mtitle)
\end{lstlisting}">

@ -57,7 +57,7 @@ hb_write -- Write a sparse matrix to a file
<BR>
<IMG
WIDTH="537" HEIGHT="16" ALIGN="BOTTOM" BORDER="0"
SRC="img155.png"
SRC="img160.png"
ALT="\begin{lstlisting}
call hb_write(a, iret, iunit, filename, key, rhs, mtitle)
\end{lstlisting}">

@ -57,7 +57,7 @@ mm_mat_read -- Read a sparse matrix from a
<BR>
<IMG
WIDTH="394" HEIGHT="16" ALIGN="BOTTOM" BORDER="0"
SRC="img156.png"
SRC="img161.png"
ALT="\begin{lstlisting}
call mm_mat_read(a, iret, iunit, filename)
\end{lstlisting}">

@ -57,7 +57,7 @@ mm_array_read -- Read a dense array from a
<BR>
<IMG
WIDTH="413" HEIGHT="16" ALIGN="BOTTOM" BORDER="0"
SRC="img157.png"
SRC="img162.png"
ALT="\begin{lstlisting}
call mm_array_read(b, iret, iunit, filename)
\end{lstlisting}">

@ -57,7 +57,7 @@ mm_mat_write -- Write a sparse matrix to a
<BR>
<IMG
WIDTH="480" HEIGHT="16" ALIGN="BOTTOM" BORDER="0"
SRC="img158.png"
SRC="img163.png"
ALT="\begin{lstlisting}
call mm_mat_write(a, mtitle, iret, iunit, filename)
\end{lstlisting}">

@ -56,7 +56,7 @@ mm_array_write -- Write a dense array from a
<BR>
<IMG
WIDTH="423" HEIGHT="16" ALIGN="BOTTOM" BORDER="0"
SRC="img159.png"
SRC="img164.png"
ALT="\begin{lstlisting}
call mm_array_write(b, iret, iunit, filename)
\end{lstlisting}">

@ -112,9 +112,9 @@ Error code: if no error, 0 is returned.
Legal inputs to this subroutine are interpreted depending on the
<SPAN CLASS="MATH"><IMG
WIDTH="41" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img160.png"
SRC="img165.png"
ALT="$ptype$"></SPAN> string as follows<A NAME="tex2html31"
HREF="footnode.html#foot7826"><SUP><SPAN CLASS="arabic">4</SPAN></SUP></A>:
HREF="footnode.html#foot7863"><SUP><SPAN CLASS="arabic">4</SPAN></SUP></A>:
<DL>
<DT><STRONG>NONE</STRONG></DT>
<DD>No preconditioning, i.e. the preconditioner is just a copy
@ -137,7 +137,7 @@ Legal inputs to this subroutine are interpreted depending on the
by the data allocation boundaries for each process; requires no
communication. Only the incomplete factorization <SPAN CLASS="MATH"><IMG
WIDTH="56" HEIGHT="32" ALIGN="MIDDLE" BORDER="0"
SRC="img161.png"
SRC="img166.png"
ALT="$ILU(0)$"></SPAN> is
currently implemented.
</DD>

@ -97,7 +97,7 @@ Intent: <B>in</B>.
<BR>
Specified as: an integer number between 0 and <SPAN CLASS="MATH"><IMG
WIDTH="49" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img162.png"
SRC="img167.png"
ALT="$np-1$"></SPAN>, in which case
the specified process will print the description, or <SPAN CLASS="MATH"><IMG
WIDTH="24" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"

@ -73,7 +73,7 @@ err = \frac{\|r_i\|}{(\|A\|\|x_i\|+\|b\|)} < eps
<IMG
WIDTH="204" HEIGHT="44" BORDER="0"
SRC="img163.png"
SRC="img168.png"
ALT="\begin{displaymath}err = \frac{\Vert r_i\Vert}{(\Vert A\Vert\Vert x_i\Vert+\Vert b\Vert)} &lt; eps \end{displaymath}">
</DIV>
<BR CLEAR="ALL">
@ -92,7 +92,7 @@ err = \frac{\|r_i\|}{\|b\|_2} < eps
<IMG
WIDTH="121" HEIGHT="44" BORDER="0"
SRC="img164.png"
SRC="img169.png"
ALT="\begin{displaymath}err = \frac{\Vert r_i\Vert}{\Vert b\Vert _2} &lt; eps \end{displaymath}">
</DIV>
<BR CLEAR="ALL">
@ -111,7 +111,7 @@ err = \frac{\|r_i\|}{\|r_0\|_2} < eps
<IMG
WIDTH="128" HEIGHT="44" BORDER="0"
SRC="img165.png"
SRC="img170.png"
ALT="\begin{displaymath}err = \frac{\Vert r_i\Vert}{\Vert r_0\Vert _2} &lt; eps \end{displaymath}">
</DIV>
<BR CLEAR="ALL">
@ -121,11 +121,11 @@ err = \frac{\|r_i\|}{\|r_0\|_2} < eps
The behaviour is controlled by the istop argument (see
later). In the above formulae, <SPAN CLASS="MATH"><IMG
WIDTH="18" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img166.png"
SRC="img171.png"
ALT="$x_i$"></SPAN> is the tentative solution and
<SPAN CLASS="MATH"><IMG
WIDTH="91" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img167.png"
SRC="img172.png"
ALT="$r_i=b-Ax_i$"></SPAN> the corresponding residual at the <SPAN CLASS="MATH"><IMG
WIDTH="9" HEIGHT="17" ALIGN="BOTTOM" BORDER="0"
SRC="img4.png"
@ -135,7 +135,7 @@ later). In the above formulae, <SPAN CLASS="MATH"><IMG
<BR>
<IMG
WIDTH="482" HEIGHT="35" ALIGN="BOTTOM" BORDER="0"
SRC="img168.png"
SRC="img173.png"
ALT="\begin{lstlisting}
call psb_krylov(method,a,prec,b,x,eps,desc_a,info,&amp;
&amp; itmax,iter,err,itrace,irst,istop,cond)
@ -169,7 +169,7 @@ call psb_krylov(method,a,prec,b,x,eps,desc_a,info,&amp;
</DD>
<DT><STRONG>FCG:</STRONG></DT>
<DD>the Flexible Conjugate Gradient method<A NAME="tex2html32"
HREF="footnode.html#foot8281"><SUP><SPAN CLASS="arabic">5</SPAN></SUP></A>;
HREF="footnode.html#foot8318"><SUP><SPAN CLASS="arabic">5</SPAN></SUP></A>;
<P>
</DD>
@ -272,25 +272,25 @@ Intent: <B>in</B>.
<BR>
Default: <SPAN CLASS="MATH"><IMG
WIDTH="99" HEIGHT="17" ALIGN="BOTTOM" BORDER="0"
SRC="img170.png"
SRC="img175.png"
ALT="$itmax = 1000$"></SPAN>.
<BR>
Specified as: an integer variable <SPAN CLASS="MATH"><IMG
WIDTH="76" HEIGHT="29" ALIGN="MIDDLE" BORDER="0"
SRC="img171.png"
SRC="img176.png"
ALT="$itmax \ge 1$"></SPAN>.
</DD>
<DT><STRONG>itrace</STRONG></DT>
<DD>If <SPAN CLASS="MATH"><IMG
WIDTH="29" HEIGHT="30" ALIGN="MIDDLE" BORDER="0"
SRC="img115.png"
SRC="img120.png"
ALT="$&gt;0$"></SPAN> print out an informational message about
convergence every <SPAN CLASS="MATH"><IMG
WIDTH="45" HEIGHT="17" ALIGN="BOTTOM" BORDER="0"
SRC="img172.png"
SRC="img177.png"
ALT="$itrace$"></SPAN> iterations. If <SPAN CLASS="MATH"><IMG
WIDTH="29" HEIGHT="13" ALIGN="BOTTOM" BORDER="0"
SRC="img173.png"
SRC="img178.png"
ALT="$=0$"></SPAN> print a message in
case of convergence failure.
<BR>
@ -302,7 +302,7 @@ Intent: <B>in</B>.
<BR>
Default: <SPAN CLASS="MATH"><IMG
WIDTH="87" HEIGHT="29" ALIGN="MIDDLE" BORDER="0"
SRC="img174.png"
SRC="img179.png"
ALT="$itrace = -1$"></SPAN>.
<BR></DD>
<DT><STRONG>irst</STRONG></DT>
@ -316,7 +316,7 @@ Intent: <B>in</B>.
<BR>
Values: <SPAN CLASS="MATH"><IMG
WIDTH="60" HEIGHT="29" ALIGN="MIDDLE" BORDER="0"
SRC="img175.png"
SRC="img180.png"
ALT="$irst&gt;0$"></SPAN>. This is employed for the BiCGSTABL or RGMRES
methods, otherwise it is ignored.
@ -377,7 +377,7 @@ Returned as: a real number.
ALT="$A$"></SPAN>; only
available with the <SPAN CLASS="MATH"><IMG
WIDTH="29" HEIGHT="14" ALIGN="BOTTOM" BORDER="0"
SRC="img176.png"
SRC="img181.png"
ALT="$CG$"></SPAN> method on real data.
<BR>
Scope: <B>global</B>

Some files were not shown because too many files have changed in this diff Show More

Loading…
Cancel
Save