Fix calls to checkvect in data exchange functions.

new-parstruct
Salvatore Filippone 6 years ago
parent 715191bb77
commit 2991c6407c

@ -129,22 +129,13 @@ subroutine psb_chalom(x,desc_a,info,jx,ik,work,tran,mode,data)
endif
ldx = size(x,1)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx,check_halo=.true.)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -319,22 +310,13 @@ subroutine psb_chalov(x,desc_a,info,work,tran,mode,data)
endif
ldx = size(x,1)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx,check_halo=.true.)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -406,8 +388,8 @@ subroutine psb_chalo_vect(x,desc_a,info,work,tran,mode,data)
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, imode,&
& err, liwork,data_
& err_act, m, n, iix, jjx, ix, ijx, nrow, ncol, lldx, &
& imode, err, liwork,data_
complex(psb_spk_),pointer :: iwork(:)
character :: tran_
character(len=20) :: name, ch_err
@ -435,11 +417,12 @@ subroutine psb_chalo_vect(x,desc_a,info,work,tran,mode,data)
endif
ix = 1
ijx = 1
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
lldx = x%get_nrows()
if (present(tran)) then
tran_ = psb_toupper(tran)
@ -457,23 +440,14 @@ subroutine psb_chalo_vect(x,desc_a,info,work,tran,mode,data)
imode = IOR(psb_swap_send_,psb_swap_recv_)
endif
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if ((info == 0).and.(lldx<ncol)) call x%reall(ncol,info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -545,7 +519,7 @@ subroutine psb_chalo_multivect(x,desc_a,info,work,tran,mode,data)
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, imode,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, ncol,lldx,imode,&
& err, liwork,data_
complex(psb_spk_),pointer :: iwork(:)
character :: tran_
@ -579,6 +553,8 @@ subroutine psb_chalo_multivect(x,desc_a,info,work,tran,mode,data)
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
lldx = x%get_nrows()
if (present(tran)) then
tran_ = psb_toupper(tran)
@ -596,23 +572,14 @@ subroutine psb_chalo_multivect(x,desc_a,info,work,tran,mode,data)
imode = IOR(psb_swap_send_,psb_swap_recv_)
endif
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if (lldx < ncol) call x%reall(ncol,x%get_ncols(),info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then

@ -139,20 +139,11 @@ subroutine psb_covrlm(x,desc_a,info,jx,ik,work,update,mode)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then
@ -327,12 +318,11 @@ subroutine psb_covrlv(x,desc_a,info,work,update,mode)
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
call psb_errpush(info,name)
end if
if(info /= 0) goto 9999
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
@ -420,13 +410,12 @@ subroutine psb_covrl_vect(x,desc_a,info,work,update,mode)
endif
ix = 1
ijx = 1
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
ldx = x%get_nrows()
k = 1
if (present(update)) then
@ -443,22 +432,14 @@ subroutine psb_covrl_vect(x,desc_a,info,work,update,mode)
do_swap = (mode_ /= 0)
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if ((info == 0).and.(ldx<ncol)) call x%reall(ncol,info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then
@ -551,6 +532,7 @@ subroutine psb_covrl_multivect(x,desc_a,info,work,update,mode)
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
ldx = x%get_nrows()
k = 1
@ -568,22 +550,14 @@ subroutine psb_covrl_multivect(x,desc_a,info,work,update,mode)
do_swap = (mode_ /= 0)
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if (ldx < ncol) call x%reall(ncol,x%get_ncols(),info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then

@ -129,22 +129,13 @@ subroutine psb_dhalom(x,desc_a,info,jx,ik,work,tran,mode,data)
endif
ldx = size(x,1)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx,check_halo=.true.)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -319,22 +310,13 @@ subroutine psb_dhalov(x,desc_a,info,work,tran,mode,data)
endif
ldx = size(x,1)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx,check_halo=.true.)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -406,8 +388,8 @@ subroutine psb_dhalo_vect(x,desc_a,info,work,tran,mode,data)
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, imode,&
& err, liwork,data_
& err_act, m, n, iix, jjx, ix, ijx, nrow, ncol, lldx, &
& imode, err, liwork,data_
real(psb_dpk_),pointer :: iwork(:)
character :: tran_
character(len=20) :: name, ch_err
@ -435,11 +417,12 @@ subroutine psb_dhalo_vect(x,desc_a,info,work,tran,mode,data)
endif
ix = 1
ijx = 1
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
lldx = x%get_nrows()
if (present(tran)) then
tran_ = psb_toupper(tran)
@ -457,23 +440,14 @@ subroutine psb_dhalo_vect(x,desc_a,info,work,tran,mode,data)
imode = IOR(psb_swap_send_,psb_swap_recv_)
endif
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if ((info == 0).and.(lldx<ncol)) call x%reall(ncol,info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -545,7 +519,7 @@ subroutine psb_dhalo_multivect(x,desc_a,info,work,tran,mode,data)
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, imode,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, ncol,lldx,imode,&
& err, liwork,data_
real(psb_dpk_),pointer :: iwork(:)
character :: tran_
@ -579,6 +553,8 @@ subroutine psb_dhalo_multivect(x,desc_a,info,work,tran,mode,data)
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
lldx = x%get_nrows()
if (present(tran)) then
tran_ = psb_toupper(tran)
@ -596,23 +572,14 @@ subroutine psb_dhalo_multivect(x,desc_a,info,work,tran,mode,data)
imode = IOR(psb_swap_send_,psb_swap_recv_)
endif
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if (lldx < ncol) call x%reall(ncol,x%get_ncols(),info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then

@ -139,20 +139,11 @@ subroutine psb_dovrlm(x,desc_a,info,jx,ik,work,update,mode)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then
@ -327,12 +318,11 @@ subroutine psb_dovrlv(x,desc_a,info,work,update,mode)
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
call psb_errpush(info,name)
end if
if(info /= 0) goto 9999
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
@ -420,13 +410,12 @@ subroutine psb_dovrl_vect(x,desc_a,info,work,update,mode)
endif
ix = 1
ijx = 1
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
ldx = x%get_nrows()
k = 1
if (present(update)) then
@ -443,22 +432,14 @@ subroutine psb_dovrl_vect(x,desc_a,info,work,update,mode)
do_swap = (mode_ /= 0)
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if ((info == 0).and.(ldx<ncol)) call x%reall(ncol,info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then
@ -551,6 +532,7 @@ subroutine psb_dovrl_multivect(x,desc_a,info,work,update,mode)
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
ldx = x%get_nrows()
k = 1
@ -568,22 +550,14 @@ subroutine psb_dovrl_multivect(x,desc_a,info,work,update,mode)
do_swap = (mode_ /= 0)
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if (ldx < ncol) call x%reall(ncol,x%get_ncols(),info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then

@ -129,22 +129,13 @@ subroutine psb_ihalom(x,desc_a,info,jx,ik,work,tran,mode,data)
endif
ldx = size(x,1)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx,check_halo=.true.)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -319,22 +310,13 @@ subroutine psb_ihalov(x,desc_a,info,work,tran,mode,data)
endif
ldx = size(x,1)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx,check_halo=.true.)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -406,8 +388,8 @@ subroutine psb_ihalo_vect(x,desc_a,info,work,tran,mode,data)
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, imode,&
& err, liwork,data_
& err_act, m, n, iix, jjx, ix, ijx, nrow, ncol, lldx, &
& imode, err, liwork,data_
integer(psb_ipk_),pointer :: iwork(:)
character :: tran_
character(len=20) :: name, ch_err
@ -435,11 +417,12 @@ subroutine psb_ihalo_vect(x,desc_a,info,work,tran,mode,data)
endif
ix = 1
ijx = 1
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
lldx = x%get_nrows()
if (present(tran)) then
tran_ = psb_toupper(tran)
@ -457,23 +440,14 @@ subroutine psb_ihalo_vect(x,desc_a,info,work,tran,mode,data)
imode = IOR(psb_swap_send_,psb_swap_recv_)
endif
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if ((info == 0).and.(lldx<ncol)) call x%reall(ncol,info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -545,7 +519,7 @@ subroutine psb_ihalo_multivect(x,desc_a,info,work,tran,mode,data)
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, imode,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, ncol,lldx,imode,&
& err, liwork,data_
integer(psb_ipk_),pointer :: iwork(:)
character :: tran_
@ -579,6 +553,8 @@ subroutine psb_ihalo_multivect(x,desc_a,info,work,tran,mode,data)
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
lldx = x%get_nrows()
if (present(tran)) then
tran_ = psb_toupper(tran)
@ -596,23 +572,14 @@ subroutine psb_ihalo_multivect(x,desc_a,info,work,tran,mode,data)
imode = IOR(psb_swap_send_,psb_swap_recv_)
endif
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if (lldx < ncol) call x%reall(ncol,x%get_ncols(),info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then

@ -139,20 +139,11 @@ subroutine psb_iovrlm(x,desc_a,info,jx,ik,work,update,mode)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then
@ -327,12 +318,11 @@ subroutine psb_iovrlv(x,desc_a,info,work,update,mode)
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
call psb_errpush(info,name)
end if
if(info /= 0) goto 9999
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
@ -420,13 +410,12 @@ subroutine psb_iovrl_vect(x,desc_a,info,work,update,mode)
endif
ix = 1
ijx = 1
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
ldx = x%get_nrows()
k = 1
if (present(update)) then
@ -443,22 +432,14 @@ subroutine psb_iovrl_vect(x,desc_a,info,work,update,mode)
do_swap = (mode_ /= 0)
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if ((info == 0).and.(ldx<ncol)) call x%reall(ncol,info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then
@ -551,6 +532,7 @@ subroutine psb_iovrl_multivect(x,desc_a,info,work,update,mode)
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
ldx = x%get_nrows()
k = 1
@ -568,22 +550,14 @@ subroutine psb_iovrl_multivect(x,desc_a,info,work,update,mode)
do_swap = (mode_ /= 0)
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if (ldx < ncol) call x%reall(ncol,x%get_ncols(),info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then

@ -129,22 +129,13 @@ subroutine psb_shalom(x,desc_a,info,jx,ik,work,tran,mode,data)
endif
ldx = size(x,1)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx,check_halo=.true.)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -319,22 +310,13 @@ subroutine psb_shalov(x,desc_a,info,work,tran,mode,data)
endif
ldx = size(x,1)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx,check_halo=.true.)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -406,8 +388,8 @@ subroutine psb_shalo_vect(x,desc_a,info,work,tran,mode,data)
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, imode,&
& err, liwork,data_
& err_act, m, n, iix, jjx, ix, ijx, nrow, ncol, lldx, &
& imode, err, liwork,data_
real(psb_spk_),pointer :: iwork(:)
character :: tran_
character(len=20) :: name, ch_err
@ -435,11 +417,12 @@ subroutine psb_shalo_vect(x,desc_a,info,work,tran,mode,data)
endif
ix = 1
ijx = 1
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
lldx = x%get_nrows()
if (present(tran)) then
tran_ = psb_toupper(tran)
@ -457,23 +440,14 @@ subroutine psb_shalo_vect(x,desc_a,info,work,tran,mode,data)
imode = IOR(psb_swap_send_,psb_swap_recv_)
endif
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if ((info == 0).and.(lldx<ncol)) call x%reall(ncol,info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -545,7 +519,7 @@ subroutine psb_shalo_multivect(x,desc_a,info,work,tran,mode,data)
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, imode,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, ncol,lldx,imode,&
& err, liwork,data_
real(psb_spk_),pointer :: iwork(:)
character :: tran_
@ -579,6 +553,8 @@ subroutine psb_shalo_multivect(x,desc_a,info,work,tran,mode,data)
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
lldx = x%get_nrows()
if (present(tran)) then
tran_ = psb_toupper(tran)
@ -596,23 +572,14 @@ subroutine psb_shalo_multivect(x,desc_a,info,work,tran,mode,data)
imode = IOR(psb_swap_send_,psb_swap_recv_)
endif
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if (lldx < ncol) call x%reall(ncol,x%get_ncols(),info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then

@ -139,20 +139,11 @@ subroutine psb_sovrlm(x,desc_a,info,jx,ik,work,update,mode)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then
@ -327,12 +318,11 @@ subroutine psb_sovrlv(x,desc_a,info,work,update,mode)
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
call psb_errpush(info,name)
end if
if(info /= 0) goto 9999
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
@ -420,13 +410,12 @@ subroutine psb_sovrl_vect(x,desc_a,info,work,update,mode)
endif
ix = 1
ijx = 1
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
ldx = x%get_nrows()
k = 1
if (present(update)) then
@ -443,22 +432,14 @@ subroutine psb_sovrl_vect(x,desc_a,info,work,update,mode)
do_swap = (mode_ /= 0)
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if ((info == 0).and.(ldx<ncol)) call x%reall(ncol,info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then
@ -551,6 +532,7 @@ subroutine psb_sovrl_multivect(x,desc_a,info,work,update,mode)
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
ldx = x%get_nrows()
k = 1
@ -568,22 +550,14 @@ subroutine psb_sovrl_multivect(x,desc_a,info,work,update,mode)
do_swap = (mode_ /= 0)
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if (ldx < ncol) call x%reall(ncol,x%get_ncols(),info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then

@ -129,22 +129,13 @@ subroutine psb_zhalom(x,desc_a,info,jx,ik,work,tran,mode,data)
endif
ldx = size(x,1)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx,check_halo=.true.)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -319,22 +310,13 @@ subroutine psb_zhalov(x,desc_a,info,work,tran,mode,data)
endif
ldx = size(x,1)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx,check_halo=.true.)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -406,8 +388,8 @@ subroutine psb_zhalo_vect(x,desc_a,info,work,tran,mode,data)
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, imode,&
& err, liwork,data_
& err_act, m, n, iix, jjx, ix, ijx, nrow, ncol, lldx, &
& imode, err, liwork,data_
complex(psb_dpk_),pointer :: iwork(:)
character :: tran_
character(len=20) :: name, ch_err
@ -435,11 +417,12 @@ subroutine psb_zhalo_vect(x,desc_a,info,work,tran,mode,data)
endif
ix = 1
ijx = 1
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
lldx = x%get_nrows()
if (present(tran)) then
tran_ = psb_toupper(tran)
@ -457,23 +440,14 @@ subroutine psb_zhalo_vect(x,desc_a,info,work,tran,mode,data)
imode = IOR(psb_swap_send_,psb_swap_recv_)
endif
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if ((info == 0).and.(lldx<ncol)) call x%reall(ncol,info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then
@ -545,7 +519,7 @@ subroutine psb_zhalo_multivect(x,desc_a,info,work,tran,mode,data)
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, imode,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, ncol,lldx,imode,&
& err, liwork,data_
complex(psb_dpk_),pointer :: iwork(:)
character :: tran_
@ -579,6 +553,8 @@ subroutine psb_zhalo_multivect(x,desc_a,info,work,tran,mode,data)
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
lldx = x%get_nrows()
if (present(tran)) then
tran_ = psb_toupper(tran)
@ -596,23 +572,14 @@ subroutine psb_zhalo_multivect(x,desc_a,info,work,tran,mode,data)
imode = IOR(psb_swap_send_,psb_swap_recv_)
endif
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if (lldx < ncol) call x%reall(ncol,x%get_ncols(),info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
liwork=nrow
if (present(work)) then
if(size(work) >= liwork) then

@ -139,20 +139,11 @@ subroutine psb_zovrlm(x,desc_a,info,jx,ik,work,update,mode)
! check vector correctness
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_chkvect'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then
@ -327,12 +318,11 @@ subroutine psb_zovrlv(x,desc_a,info,work,update,mode)
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
call psb_errpush(info,name)
end if
if(info /= 0) goto 9999
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
@ -420,13 +410,12 @@ subroutine psb_zovrl_vect(x,desc_a,info,work,update,mode)
endif
ix = 1
ijx = 1
m = desc_a%get_global_rows()
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
ldx = x%get_nrows()
k = 1
if (present(update)) then
@ -443,22 +432,14 @@ subroutine psb_zovrl_vect(x,desc_a,info,work,update,mode)
do_swap = (mode_ /= 0)
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if ((info == 0).and.(ldx<ncol)) call x%reall(ncol,info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then
@ -551,6 +532,7 @@ subroutine psb_zovrl_multivect(x,desc_a,info,work,update,mode)
n = desc_a%get_global_cols()
nrow = desc_a%get_local_rows()
ncol = desc_a%get_local_cols()
ldx = x%get_nrows()
k = 1
@ -568,22 +550,14 @@ subroutine psb_zovrl_multivect(x,desc_a,info,work,update,mode)
do_swap = (mode_ /= 0)
! check vector correctness
call psb_chkvect(m,ione,x%get_nrows(),ix,ijx,desc_a,info,iix,jjx)
if (ldx < ncol) call x%reall(ncol,x%get_ncols(),info)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect'
info=psb_err_from_subroutine_ ; ch_err='psb_reall'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if (iix /= 1) then
info=psb_err_ix_n1_iy_n1_unsupported_
call psb_errpush(info,name)
end if
err=info
call psb_errcomm(ictxt,err)
if(err /= 0) goto 9999
! check for presence/size of a work area
liwork=ncol
if (present(work)) then

Loading…
Cancel
Save