|
|
|
@ -50,7 +50,7 @@
|
|
|
|
|
subroutine psb_dspmm(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
& trans, k, jx, jy, work, doswap)
|
|
|
|
|
|
|
|
|
|
use psb_dspmat_type
|
|
|
|
|
use psb_spmat_type
|
|
|
|
|
use psb_serial_mod
|
|
|
|
|
use psb_descriptor_type
|
|
|
|
|
use psb_comm_mod
|
|
|
|
@ -59,30 +59,33 @@ subroutine psb_dspmm(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
|
|
real(kind(1.D0)), intent(in) :: alpha, beta
|
|
|
|
|
real(kind(1.d0)), intent(inout) :: x(:,:)
|
|
|
|
|
real(kind(1.d0)), intent(inout) :: y(:,:)
|
|
|
|
|
real(kind(1.d0)), intent(inout), target :: x(:,:)
|
|
|
|
|
real(kind(1.d0)), intent(inout), target :: y(:,:)
|
|
|
|
|
type(psb_dspmat_type), intent(in) :: a
|
|
|
|
|
type(psb_desc_type), intent(in) :: desc_a
|
|
|
|
|
integer, intent(out) :: info
|
|
|
|
|
real(kind(1.d0)), intent(inout), optional :: work(:)
|
|
|
|
|
real(kind(1.d0)), optional, pointer :: work(:)
|
|
|
|
|
character, intent(in), optional :: trans
|
|
|
|
|
integer, intent(in), optional :: k, jx, jy,doswap
|
|
|
|
|
|
|
|
|
|
! locals
|
|
|
|
|
integer :: int_err(5), icontxt, nprow, npcol, me, mycol,&
|
|
|
|
|
& err_act, n, iix, jjx, ia, ja, iia, jja, temp(2)
|
|
|
|
|
integer :: int_err(5), icontxt, nprow, npcol, myrow, mycol,&
|
|
|
|
|
& err_act, n, iix, jjx, ia, ja, iia, jja, temp(2), ix, iy, ik, ijx, ijy,&
|
|
|
|
|
& idoswap, m, nrow, ncol, lldx, lldy, liwork, llwork, iiy, jjy,&
|
|
|
|
|
& i, ib, ib1
|
|
|
|
|
integer, parameter :: nb=4
|
|
|
|
|
real(kind(1.d0)),pointer :: tmpx(:), xp(:,:), yp(:,:)
|
|
|
|
|
real(kind(1.d0)),pointer :: tmpx(:), xp(:,:), yp(:,:), iwork(:)
|
|
|
|
|
character :: itrans
|
|
|
|
|
character(len=20) :: name, ch_err
|
|
|
|
|
|
|
|
|
|
name='psb_dspmm'
|
|
|
|
|
info=0
|
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
|
|
|
|
|
|
icontxt=desc_data(psb_ctxt_)
|
|
|
|
|
icontxt=desc_a%matrix_data(psb_ctxt_)
|
|
|
|
|
|
|
|
|
|
! check on blacs grid
|
|
|
|
|
call blacs_gridinfo(icontxt, nprow, npcol, me, mypcol)
|
|
|
|
|
call blacs_gridinfo(icontxt, nprow, npcol, myrow, mycol)
|
|
|
|
|
if (nprow == -1) then
|
|
|
|
|
info = 2010
|
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
@ -112,9 +115,9 @@ subroutine psb_dspmm(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
if (present(doswap)) then
|
|
|
|
|
doswap_ = doswap
|
|
|
|
|
idoswap = doswap
|
|
|
|
|
else
|
|
|
|
|
doswap_ = 1
|
|
|
|
|
idoswap = 1
|
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
if (present(k)) then
|
|
|
|
@ -140,8 +143,8 @@ subroutine psb_dspmm(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
itrans = 'N'
|
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
m = desc_data(m_)
|
|
|
|
|
n = desc_data(n_)
|
|
|
|
|
m = desc_a%matrix_data(psb_m_)
|
|
|
|
|
n = desc_a%matrix_data(psb_n_)
|
|
|
|
|
nrow = desc_a%matrix_data(psb_n_row_)
|
|
|
|
|
ncol = desc_a%matrix_data(psb_n_col_)
|
|
|
|
|
lldx = size(x,1)
|
|
|
|
@ -193,8 +196,8 @@ subroutine psb_dspmm(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
! checking for vectors correctness
|
|
|
|
|
call psb_chkvect(n,ik,size(x,1),ix,ijx,desc_data%matrix_data,info,iix,jjx)
|
|
|
|
|
call psb_chkvect(m,ik,size(y,1),iy,ijy,desc_data%matrix_data,info,iiy,jjy)
|
|
|
|
|
call psb_chkvect(n,ik,size(x,1),ix,ijx,desc_a%matrix_data,info,iix,jjx)
|
|
|
|
|
call psb_chkvect(m,ik,size(y,1),iy,ijy,desc_a%matrix_data,info,iiy,jjy)
|
|
|
|
|
if(info.ne.0) then
|
|
|
|
|
info=4010
|
|
|
|
|
ch_err='psb_chkvect'
|
|
|
|
@ -209,12 +212,12 @@ subroutine psb_dspmm(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
goto 9999
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
if(doswap_.lt.0) x(nrow:ncol,1:ik)=0.d0
|
|
|
|
|
if(idoswap.lt.0) x(nrow:ncol,1:ik)=0.d0
|
|
|
|
|
|
|
|
|
|
ib1=min(nb,ik)
|
|
|
|
|
xp => x(iix:lldx,jjx:jjx+ib1-1)
|
|
|
|
|
if(doswap_.gt.0)&
|
|
|
|
|
& call psi_swapdata(ior(SWAP_SEND,SWAP_RECV),&
|
|
|
|
|
if(idoswap.gt.0)&
|
|
|
|
|
& call psi_swapdata(ior(psb_swap_send_,psb_swap_recv_),&
|
|
|
|
|
& ib1,dzero,xp,desc_a,iwork,info)
|
|
|
|
|
!!$ & call PSI_dSwapData(ior(SWAP_SEND,SWAP_RECV),ib1,&
|
|
|
|
|
!!$ & dzero,x(iix,jjx),lldx,desc_a%matrix_data,&
|
|
|
|
@ -225,8 +228,8 @@ subroutine psb_dspmm(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
ib=ib1
|
|
|
|
|
ib1 = max(0,min(nb,(ik)-(i-1+ib)))
|
|
|
|
|
xp => x(iix:lldx,jjx+i+ib-1:jjx+i+ib+ib1-2)
|
|
|
|
|
if((ib1.gt.0).and.(doswap_.gt.0))&
|
|
|
|
|
& call psi_swapdata(SWAP_SEND_,ib1,&
|
|
|
|
|
if((ib1.gt.0).and.(idoswap.gt.0))&
|
|
|
|
|
& call psi_swapdata(psb_swap_send_,ib1,&
|
|
|
|
|
& dzero,xp,desc_a,iwork,info)
|
|
|
|
|
!!$ & call PSI_dSwapData(SWAP_SEND,ib1,&
|
|
|
|
|
!!$ & dzero,x(iix,jjx+i+ib-1),lldx,desc_a%matrix_data,&
|
|
|
|
@ -234,20 +237,20 @@ subroutine psb_dspmm(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
if(info.ne.0) exit blk
|
|
|
|
|
|
|
|
|
|
! local Matrix-vector product
|
|
|
|
|
call dcsmm(itran,nrow,ib,ncol,alpha,a%pr,a%fida,&
|
|
|
|
|
call dcsmm(itrans,nrow,ib,ncol,alpha,a%pr,a%fida,&
|
|
|
|
|
& a%descra,a%aspk,a%ia1,a%ia2,a%infoa,a%pl,&
|
|
|
|
|
& x(iix,jjx+i-1),lldx,beta,y(iiy,jjy+i-1),lldy,&
|
|
|
|
|
& iwork,liwork,info)
|
|
|
|
|
if(info.ne.0) exit blk
|
|
|
|
|
|
|
|
|
|
if((ib1.gt.0).and.(doswap_.gt.0))&
|
|
|
|
|
& call psi_swapdata(SWAP_SEND_,ib1,&
|
|
|
|
|
if((ib1.gt.0).and.(idoswap.gt.0))&
|
|
|
|
|
& call psi_swapdata(psb_swap_send_,ib1,&
|
|
|
|
|
& dzero,xp,desc_a,iwork,info)
|
|
|
|
|
!!$ & call PSI_dSwapData(SWAP_RECV,ib1,&
|
|
|
|
|
!!$ & dzero,x(iix,jjx+i+ib-1),lldx,desc_a%matrix_data,&
|
|
|
|
|
!!$ & desc_a%halo_index,iwork,liwork,info)
|
|
|
|
|
if(info.ne.0) exit blk
|
|
|
|
|
end do
|
|
|
|
|
end do blk
|
|
|
|
|
|
|
|
|
|
if(info.ne.0) then
|
|
|
|
|
info = 4011
|
|
|
|
@ -264,15 +267,15 @@ subroutine psb_dspmm(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
goto 9999
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
if(desc_as%ovrlap_elem(1).ne.-1) then
|
|
|
|
|
if(desc_a%ovrlap_elem(1).ne.-1) then
|
|
|
|
|
info = 3070
|
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
|
goto 9999
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
! checking for vectors correctness
|
|
|
|
|
call psb_chkvect(m,ik,size(x,1),ix,ijx,desc_data%matrix_data,info,iix,jjx)
|
|
|
|
|
call psb_chkvect(n,ik,size(y,1),iy,ijy,desc_data%matrix_data,info,iiy,jjy)
|
|
|
|
|
call psb_chkvect(m,ik,size(x,1),ix,ijx,desc_a%matrix_data,info,iix,jjx)
|
|
|
|
|
call psb_chkvect(n,ik,size(y,1),iy,ijy,desc_a%matrix_data,info,iiy,jjy)
|
|
|
|
|
if(info.ne.0) then
|
|
|
|
|
info=4010
|
|
|
|
|
ch_err='psb_chkvect'
|
|
|
|
@ -287,10 +290,10 @@ subroutine psb_dspmm(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
goto 9999
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
if(doswap_.lt.0) y(nrow:ncol,1:ik)=0.d0
|
|
|
|
|
if(idoswap.lt.0) y(nrow:ncol,1:ik)=0.d0
|
|
|
|
|
|
|
|
|
|
! local Matrix-vector product
|
|
|
|
|
call dcsmm(itran,ncol,ik,nrow,alpha,a%pr,a%fida,&
|
|
|
|
|
call dcsmm(itrans,ncol,ik,nrow,alpha,a%pr,a%fida,&
|
|
|
|
|
& a%descra,a%aspk,a%ia1,a%ia2,a%infoa,a%pl,&
|
|
|
|
|
& x(iix,jjx),lldx,beta,y(iiy,jjy),lldy,&
|
|
|
|
|
& iwork,liwork,info)
|
|
|
|
@ -302,8 +305,8 @@ subroutine psb_dspmm(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
yp => y(iiy:lldy,jjy:jjy+ik-1)
|
|
|
|
|
if(doswap_.gt.0)&
|
|
|
|
|
& call psi_swaptran(ior(SWAP_SEND,SWAP_RECV),&
|
|
|
|
|
if(idoswap.gt.0)&
|
|
|
|
|
& call psi_swaptran(ior(psb_swap_send_,psb_swap_recv_),&
|
|
|
|
|
& ik,done,yp,desc_a,iwork,info)
|
|
|
|
|
!!$ & call PSI_dSwapTran(ior(SWAP_SEND,SWAP_RECV),&
|
|
|
|
|
!!$ & ik,done,y(iiy,jjy),lldy,desc_a%matrix_data,&
|
|
|
|
@ -360,7 +363,7 @@ end subroutine psb_dspmm
|
|
|
|
|
subroutine psb_dspmv(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
& trans, work, doswap)
|
|
|
|
|
|
|
|
|
|
use psb_dspmat_type
|
|
|
|
|
use psb_spmat_type
|
|
|
|
|
use psb_serial_mod
|
|
|
|
|
use psb_descriptor_type
|
|
|
|
|
use psb_comm_mod
|
|
|
|
@ -369,30 +372,33 @@ subroutine psb_dspmv(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
|
|
real(kind(1.D0)), intent(in) :: alpha, beta
|
|
|
|
|
real(kind(1.d0)), intent(inout) :: x(:)
|
|
|
|
|
real(kind(1.d0)), intent(inout) :: y(:)
|
|
|
|
|
real(kind(1.d0)), intent(inout), target :: x(:)
|
|
|
|
|
real(kind(1.d0)), intent(inout), target :: y(:)
|
|
|
|
|
type(psb_dspmat_type), intent(in) :: a
|
|
|
|
|
type(psb_desc_type), intent(in) :: desc_a
|
|
|
|
|
integer, intent(out) :: info
|
|
|
|
|
real(kind(1.d0)), intent(inout), optional :: work(:)
|
|
|
|
|
real(kind(1.d0)), optional, pointer :: work(:)
|
|
|
|
|
character, intent(in), optional :: trans
|
|
|
|
|
integer, intent(in), optional :: doswap
|
|
|
|
|
|
|
|
|
|
! locals
|
|
|
|
|
integer :: int_err(5), icontxt, nprow, npcol, me, mycol,&
|
|
|
|
|
& err_act, n, iix, jjx, ia, ja, iia, jja, temp(2)
|
|
|
|
|
integer :: int_err(5), icontxt, nprow, npcol, myrow, mycol,&
|
|
|
|
|
& err_act, n, iix, jjx, ia, ja, iia, jja, temp(2), ix, iy, ik, ijx, ijy,&
|
|
|
|
|
& idoswap, m, nrow, ncol, lldx, lldy, liwork, llwork, jx, jy, iiy, jjy,&
|
|
|
|
|
& i, ib, ib1
|
|
|
|
|
integer, parameter :: nb=4
|
|
|
|
|
real(kind(1.d0)),pointer :: tmpx(:)
|
|
|
|
|
real(kind(1.d0)),pointer :: tmpx(:), iwork(:), xp(:), yp(:)
|
|
|
|
|
character :: itrans
|
|
|
|
|
character(len=20) :: name, ch_err
|
|
|
|
|
|
|
|
|
|
name='psb_dspmv'
|
|
|
|
|
info=0
|
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
|
|
|
|
|
|
icontxt=desc_data(psb_ctxt_)
|
|
|
|
|
icontxt=desc_a%matrix_data(psb_ctxt_)
|
|
|
|
|
|
|
|
|
|
! check on blacs grid
|
|
|
|
|
call blacs_gridinfo(icontxt, nprow, npcol, me, mypcol)
|
|
|
|
|
call blacs_gridinfo(icontxt, nprow, npcol, myrow, mycol)
|
|
|
|
|
if (nprow == -1) then
|
|
|
|
|
info = 2010
|
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
@ -413,9 +419,9 @@ subroutine psb_dspmv(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
ik = 1
|
|
|
|
|
|
|
|
|
|
if (present(doswap)) then
|
|
|
|
|
doswap_ = doswap
|
|
|
|
|
idoswap = doswap
|
|
|
|
|
else
|
|
|
|
|
doswap_ = 1
|
|
|
|
|
idoswap = 1
|
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
if (present(trans)) then
|
|
|
|
@ -434,8 +440,8 @@ subroutine psb_dspmv(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
itrans = 'N'
|
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
m = desc_data(m_)
|
|
|
|
|
n = desc_data(n_)
|
|
|
|
|
m = desc_a%matrix_data(psb_m_)
|
|
|
|
|
n = desc_a%matrix_data(psb_n_)
|
|
|
|
|
nrow = desc_a%matrix_data(psb_n_row_)
|
|
|
|
|
ncol = desc_a%matrix_data(psb_n_col_)
|
|
|
|
|
lldx = size(x,1)
|
|
|
|
@ -486,8 +492,8 @@ subroutine psb_dspmv(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
! checking for vectors correctness
|
|
|
|
|
call psb_chkvect(n,ik,size(x),ix,jx,desc_data%matrix_data,info,iix,jjx)
|
|
|
|
|
call psb_chkvect(m,ik,size(y),iy,jy,desc_data%matrix_data,info,iiy,jjy)
|
|
|
|
|
call psb_chkvect(n,ik,size(x),ix,jx,desc_a%matrix_data,info,iix,jjx)
|
|
|
|
|
call psb_chkvect(m,ik,size(y),iy,jy,desc_a%matrix_data,info,iiy,jjy)
|
|
|
|
|
if(info.ne.0) then
|
|
|
|
|
info=4010
|
|
|
|
|
ch_err='psb_chkvect'
|
|
|
|
@ -502,23 +508,21 @@ subroutine psb_dspmv(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
goto 9999
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
if(doswap_.lt.0) then
|
|
|
|
|
x(nrow:ncol,1:ik)=0.d0
|
|
|
|
|
if(idoswap.lt.0) then
|
|
|
|
|
x(nrow:ncol)=0.d0
|
|
|
|
|
else
|
|
|
|
|
call psi_swapdata(ior(SWAP_SEND,SWAP_RECV),&
|
|
|
|
|
& dzero,xp,desc_a,iwork,info)
|
|
|
|
|
call psi_swapdata(ior(psb_swap_send_,psb_swap_recv_),&
|
|
|
|
|
& dzero,x,desc_a,iwork,info)
|
|
|
|
|
!!$ call PSI_dSwapData(ior(SWAP_SEND,SWAP_RECV),1,&
|
|
|
|
|
!!$ & dzero,x(iix,jjx),lldx,desc_a%matrix_data,&
|
|
|
|
|
!!$ & desc_a%halo_index,iwork,liwork,info)
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
! local Matrix-vector product
|
|
|
|
|
call dcsmm(itran,nrow,ib,ncol,alpha,a%pr,a%fida,&
|
|
|
|
|
call dcsmm(itrans,nrow,ib,ncol,alpha,a%pr,a%fida,&
|
|
|
|
|
& a%descra,a%aspk,a%ia1,a%ia2,a%infoa,a%pl,&
|
|
|
|
|
& xp(iix),lldx,beta,yp(iiy),lldy,&
|
|
|
|
|
& x(iix),lldx,beta,y(iiy),lldy,&
|
|
|
|
|
& iwork,liwork,info)
|
|
|
|
|
if(info.ne.0) exit blk
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if(info.ne.0) then
|
|
|
|
|
info = 4011
|
|
|
|
@ -535,15 +539,15 @@ subroutine psb_dspmv(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
goto 9999
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
if(desc_as%ovrlap_elem(1).ne.-1) then
|
|
|
|
|
if(desc_a%ovrlap_elem(1).ne.-1) then
|
|
|
|
|
info = 3070
|
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
|
goto 9999
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
! checking for vectors correctness
|
|
|
|
|
call psb_chkvect(m,ik,size(x),ix,jx,desc_data%matrix_data,info,iix,jjx)
|
|
|
|
|
call psb_chkvect(n,ik,size(y),iy,jy,desc_data%matrix_data,info,iiy,jjy)
|
|
|
|
|
call psb_chkvect(m,ik,size(x),ix,jx,desc_a%matrix_data,info,iix,jjx)
|
|
|
|
|
call psb_chkvect(n,ik,size(y),iy,jy,desc_a%matrix_data,info,iiy,jjy)
|
|
|
|
|
if(info.ne.0) then
|
|
|
|
|
info=4010
|
|
|
|
|
ch_err='psb_chkvect'
|
|
|
|
@ -561,10 +565,10 @@ subroutine psb_dspmv(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
xp => x(iix:lldx)
|
|
|
|
|
yp => x(iiy:lldy)
|
|
|
|
|
|
|
|
|
|
if(doswap_.lt.0) y(nrow:ncol,1:ik)=0.d0
|
|
|
|
|
if(idoswap.lt.0) y(nrow:ncol)=0.d0
|
|
|
|
|
|
|
|
|
|
! local Matrix-vector product
|
|
|
|
|
call dcsmm(itran,ncol,ik,nrow,alpha,a%pr,a%fida,&
|
|
|
|
|
call dcsmm(itrans,ncol,ik,nrow,alpha,a%pr,a%fida,&
|
|
|
|
|
& a%descra,a%aspk,a%ia1,a%ia2,a%infoa,a%pl,&
|
|
|
|
|
& x(iix),lldx,beta,y(iiy),lldy,&
|
|
|
|
|
& iwork,liwork,info)
|
|
|
|
@ -575,8 +579,8 @@ subroutine psb_dspmv(alpha,a,x,beta,y,desc_a,info,&
|
|
|
|
|
goto 9999
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
if(doswap_.gt.0)&
|
|
|
|
|
$ call psi_swaptran(ior(SWAP_SEND,SWAP_RECV),&
|
|
|
|
|
if(idoswap.gt.0)&
|
|
|
|
|
& call psi_swaptran(ior(psb_swap_send_,psb_swap_recv_),&
|
|
|
|
|
& done,yp,desc_a,iwork,info)
|
|
|
|
|
!!$ & call PSI_dSwapTran(ior(SWAP_SEND,SWAP_RECV),&
|
|
|
|
|
!!$ & ik,done,y(iiy,jjy),lldy,desc_a%matrix_data,&
|
|
|
|
|