|
|
@ -39,39 +39,34 @@
|
|
|
|
! where sub( X ) denotes X(1:N,JX:).
|
|
|
|
! where sub( X ) denotes X(1:N,JX:).
|
|
|
|
!
|
|
|
|
!
|
|
|
|
! Arguments:
|
|
|
|
! Arguments:
|
|
|
|
! x(:,:) - real The input vector.
|
|
|
|
! x(:,:) - real The input vector.
|
|
|
|
! desc_a - type(psb_desc_type). The communication descriptor.
|
|
|
|
! desc_a - type(psb_desc_type). The communication descriptor.
|
|
|
|
! info - integer. Return code
|
|
|
|
! info - integer. Return code
|
|
|
|
! jx - integer(optional). The column offset.
|
|
|
|
! jx - integer(optional). The column offset.
|
|
|
|
!
|
|
|
|
!
|
|
|
|
function psb_damax (x,desc_a, info, jx)
|
|
|
|
function psb_damax(x,desc_a, info, jx) result(res)
|
|
|
|
use psb_penv_mod
|
|
|
|
use psb_base_mod, psb_protect_name => psb_damax
|
|
|
|
use psb_serial_mod
|
|
|
|
|
|
|
|
use psb_descriptor_type
|
|
|
|
|
|
|
|
use psb_check_mod
|
|
|
|
|
|
|
|
use psb_error_mod
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
|
|
|
|
real(psb_dpk_), intent(in) :: x(:,:)
|
|
|
|
real(psb_dpk_), intent(in) :: x(:,:)
|
|
|
|
type(psb_desc_type), intent(in) :: desc_a
|
|
|
|
type(psb_desc_type), intent(in) :: desc_a
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
integer(psb_ipk_), optional, intent(in) :: jx
|
|
|
|
integer(psb_ipk_), optional, intent(in) :: jx
|
|
|
|
real(psb_dpk_) :: psb_damax
|
|
|
|
real(psb_dpk_) :: res
|
|
|
|
|
|
|
|
|
|
|
|
! locals
|
|
|
|
! locals
|
|
|
|
integer(psb_ipk_) :: ictxt, np, me,&
|
|
|
|
integer(psb_ipk_) :: ictxt, np, me,&
|
|
|
|
& err_act, iix, jjx, ix, ijx, m, imax, idamax
|
|
|
|
& err_act, iix, jjx, ix, ijx, m, ldx
|
|
|
|
real(psb_dpk_) :: amax
|
|
|
|
character(len=20) :: name, ch_err
|
|
|
|
character(len=20) :: name, ch_err
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
name='psb_damax'
|
|
|
|
name='psb_damax'
|
|
|
|
if(psb_get_errstatus() /= 0) return
|
|
|
|
if(psb_get_errstatus() /= 0) return
|
|
|
|
info=psb_success_
|
|
|
|
info=psb_success_
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
|
|
|
|
|
|
|
|
amax=0.d0
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
ictxt=desc_a%get_context()
|
|
|
|
ictxt = desc_a%get_context()
|
|
|
|
|
|
|
|
|
|
|
|
call psb_info(ictxt, me, np)
|
|
|
|
call psb_info(ictxt, me, np)
|
|
|
|
if (np == -1) then
|
|
|
|
if (np == -1) then
|
|
|
@ -79,42 +74,40 @@ function psb_damax (x,desc_a, info, jx)
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
goto 9999
|
|
|
|
goto 9999
|
|
|
|
endif
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
|
|
ix = 1
|
|
|
|
ix = 1
|
|
|
|
if (present(jx)) then
|
|
|
|
if (present(jx)) then
|
|
|
|
ijx = jx
|
|
|
|
ijx = jx
|
|
|
|
else
|
|
|
|
else
|
|
|
|
ijx = 1
|
|
|
|
ijx = 1
|
|
|
|
endif
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
|
|
m = desc_a%get_global_rows()
|
|
|
|
m = desc_a%get_global_rows()
|
|
|
|
|
|
|
|
ldx = size(x,1)
|
|
|
|
|
|
|
|
|
|
|
|
call psb_chkvect(m,1,size(x,1),ix,ijx,desc_a,info,iix,jjx)
|
|
|
|
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
|
|
|
|
if(info /= psb_success_) then
|
|
|
|
if(info /= psb_success_) then
|
|
|
|
info=psb_err_from_subroutine_
|
|
|
|
info=psb_err_from_subroutine_
|
|
|
|
ch_err='psb_chkvect'
|
|
|
|
ch_err='psb_chkvect'
|
|
|
|
call psb_errpush(info,name,a_err=ch_err)
|
|
|
|
call psb_errpush(info,name,a_err=ch_err)
|
|
|
|
goto 9999
|
|
|
|
goto 9999
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
if (iix /= 1) then
|
|
|
|
if (iix /= 1) then
|
|
|
|
info=psb_err_ix_n1_iy_n1_unsupported_
|
|
|
|
info=psb_err_ix_n1_iy_n1_unsupported_
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
goto 9999
|
|
|
|
goto 9999
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
! compute local max
|
|
|
|
! compute local max
|
|
|
|
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
|
|
|
|
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
|
|
|
|
imax=idamax(desc_a%get_local_rows()-iix+1,x(iix,jjx),1)
|
|
|
|
res = psb_amax(desc_a%get_local_rows()-iix+1,x(:,jjx))
|
|
|
|
amax=abs(x(iix+imax-1,jjx))
|
|
|
|
|
|
|
|
else
|
|
|
|
else
|
|
|
|
amax = dzero
|
|
|
|
res = dzero
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
! compute global max
|
|
|
|
! compute global max
|
|
|
|
call psb_amx(ictxt, amax)
|
|
|
|
call psb_amx(ictxt, res)
|
|
|
|
|
|
|
|
|
|
|
|
psb_damax=amax
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
return
|
|
|
|
return
|
|
|
@ -123,8 +116,8 @@ function psb_damax (x,desc_a, info, jx)
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
|
|
|
|
|
|
|
|
if (err_act == psb_act_abort_) then
|
|
|
|
if (err_act == psb_act_abort_) then
|
|
|
|
call psb_error(ictxt)
|
|
|
|
call psb_error(ictxt)
|
|
|
|
return
|
|
|
|
return
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
return
|
|
|
|
return
|
|
|
|
end function psb_damax
|
|
|
|
end function psb_damax
|
|
|
@ -162,7 +155,7 @@ end function psb_damax
|
|
|
|
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
|
|
|
|
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
|
|
|
|
!!$ POSSIBILITY OF SUCH DAMAGE.
|
|
|
|
!!$ POSSIBILITY OF SUCH DAMAGE.
|
|
|
|
!!$
|
|
|
|
!!$
|
|
|
|
!!$
|
|
|
|
!!$
|
|
|
|
!
|
|
|
|
!
|
|
|
|
! Function: psb_damaxv
|
|
|
|
! Function: psb_damaxv
|
|
|
|
! Searches the absolute max of X.
|
|
|
|
! Searches the absolute max of X.
|
|
|
@ -170,27 +163,24 @@ end function psb_damax
|
|
|
|
! normi := max(abs(X(i))
|
|
|
|
! normi := max(abs(X(i))
|
|
|
|
!
|
|
|
|
!
|
|
|
|
! Arguments:
|
|
|
|
! Arguments:
|
|
|
|
! x(:) - real The input vector.
|
|
|
|
! x(:) - real The input vector.
|
|
|
|
! desc_a - type(psb_desc_type). The communication descriptor.
|
|
|
|
! desc_a - type(psb_desc_type). The communication descriptor.
|
|
|
|
! info - integer. Return code
|
|
|
|
! info - integer. Return code
|
|
|
|
!
|
|
|
|
!
|
|
|
|
function psb_damaxv (x,desc_a, info)
|
|
|
|
function psb_damaxv (x,desc_a, info) result(res)
|
|
|
|
use psb_penv_mod
|
|
|
|
use psb_base_mod, psb_protect_name => psb_damaxv
|
|
|
|
use psb_serial_mod
|
|
|
|
|
|
|
|
use psb_descriptor_type
|
|
|
|
|
|
|
|
use psb_check_mod
|
|
|
|
|
|
|
|
use psb_error_mod
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
|
|
|
|
real(psb_dpk_), intent(in) :: x(:)
|
|
|
|
real(psb_dpk_), intent(in) :: x(:)
|
|
|
|
type(psb_desc_type), intent(in) :: desc_a
|
|
|
|
type(psb_desc_type), intent(in) :: desc_a
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
real(psb_dpk_) :: psb_damaxv
|
|
|
|
real(psb_dpk_) :: res
|
|
|
|
|
|
|
|
|
|
|
|
! locals
|
|
|
|
! locals
|
|
|
|
integer(psb_ipk_) :: ictxt, np, me,&
|
|
|
|
integer(psb_ipk_) :: ictxt, np, me,&
|
|
|
|
& err_act, iix, jjx, jx, ix, m, imax, idamax
|
|
|
|
& err_act, iix, jjx, jx, ix, m, ldx
|
|
|
|
real(psb_dpk_) :: amax
|
|
|
|
|
|
|
|
character(len=20) :: name, ch_err
|
|
|
|
character(len=20) :: name, ch_err
|
|
|
|
|
|
|
|
|
|
|
|
name='psb_damaxv'
|
|
|
|
name='psb_damaxv'
|
|
|
@ -198,7 +188,6 @@ function psb_damaxv (x,desc_a, info)
|
|
|
|
info=psb_success_
|
|
|
|
info=psb_success_
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
|
|
|
|
|
|
|
|
amax=0.d0
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
ictxt=desc_a%get_context()
|
|
|
|
ictxt=desc_a%get_context()
|
|
|
|
|
|
|
|
|
|
|
@ -208,38 +197,36 @@ function psb_damaxv (x,desc_a, info)
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
goto 9999
|
|
|
|
goto 9999
|
|
|
|
endif
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
|
|
ix = 1
|
|
|
|
ix = 1
|
|
|
|
jx = 1
|
|
|
|
jx = 1
|
|
|
|
|
|
|
|
|
|
|
|
m = desc_a%get_global_rows()
|
|
|
|
m = desc_a%get_global_rows()
|
|
|
|
|
|
|
|
ldx = size(x,1)
|
|
|
|
|
|
|
|
|
|
|
|
call psb_chkvect(m,1,size(x,1),ix,jx,desc_a,info,iix,jjx)
|
|
|
|
call psb_chkvect(m,ione,ldx,ix,jx,desc_a,info,iix,jjx)
|
|
|
|
if(info /= psb_success_) then
|
|
|
|
if(info /= psb_success_) then
|
|
|
|
info=psb_err_from_subroutine_
|
|
|
|
info=psb_err_from_subroutine_
|
|
|
|
ch_err='psb_chkvect'
|
|
|
|
ch_err='psb_chkvect'
|
|
|
|
call psb_errpush(info,name,a_err=ch_err)
|
|
|
|
call psb_errpush(info,name,a_err=ch_err)
|
|
|
|
goto 9999
|
|
|
|
goto 9999
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
if (iix /= 1) then
|
|
|
|
if (iix /= 1) then
|
|
|
|
info=psb_err_ix_n1_iy_n1_unsupported_
|
|
|
|
info=psb_err_ix_n1_iy_n1_unsupported_
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
goto 9999
|
|
|
|
goto 9999
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
! compute local max
|
|
|
|
! compute local max
|
|
|
|
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
|
|
|
|
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
|
|
|
|
imax=idamax(desc_a%get_local_rows()-iix+1,x(iix),1)
|
|
|
|
res = psb_amax(desc_a%get_local_rows()-iix+1,x)
|
|
|
|
amax=abs(x(iix+imax-1))
|
|
|
|
|
|
|
|
else
|
|
|
|
else
|
|
|
|
amax = dzero
|
|
|
|
res = dzero
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
! compute global max
|
|
|
|
! compute global max
|
|
|
|
call psb_amx(ictxt, amax)
|
|
|
|
call psb_amx(ictxt, res)
|
|
|
|
|
|
|
|
|
|
|
|
psb_damaxv=amax
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
return
|
|
|
|
return
|
|
|
@ -248,12 +235,13 @@ function psb_damaxv (x,desc_a, info)
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
|
|
|
|
|
|
|
|
if (err_act == psb_act_abort_) then
|
|
|
|
if (err_act == psb_act_abort_) then
|
|
|
|
call psb_error(ictxt)
|
|
|
|
call psb_error(ictxt)
|
|
|
|
return
|
|
|
|
return
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
return
|
|
|
|
return
|
|
|
|
end function psb_damaxv
|
|
|
|
end function psb_damaxv
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
function psb_damax_vect(x, desc_a, info) result(res)
|
|
|
|
function psb_damax_vect(x, desc_a, info) result(res)
|
|
|
|
use psb_penv_mod
|
|
|
|
use psb_penv_mod
|
|
|
|
use psb_serial_mod
|
|
|
|
use psb_serial_mod
|
|
|
@ -266,20 +254,18 @@ function psb_damax_vect(x, desc_a, info) result(res)
|
|
|
|
real(psb_dpk_) :: res
|
|
|
|
real(psb_dpk_) :: res
|
|
|
|
type(psb_d_vect_type), intent (inout) :: x
|
|
|
|
type(psb_d_vect_type), intent (inout) :: x
|
|
|
|
type(psb_desc_type), intent (in) :: desc_a
|
|
|
|
type(psb_desc_type), intent (in) :: desc_a
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
|
|
|
|
|
|
|
|
! locals
|
|
|
|
! locals
|
|
|
|
integer(psb_ipk_) :: ictxt, np, me,&
|
|
|
|
integer(psb_ipk_) :: ictxt, np, me,&
|
|
|
|
& err_act, iix, jjx, jx, ix, m, imax, idamax
|
|
|
|
& err_act, iix, jjx, jx, ix, m
|
|
|
|
real(psb_dpk_) :: amax
|
|
|
|
character(len=20) :: name, ch_err
|
|
|
|
character(len=20) :: name, ch_err
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
name='psb_damaxv'
|
|
|
|
name='psb_damaxv'
|
|
|
|
if(psb_get_errstatus() /= 0) return
|
|
|
|
if(psb_get_errstatus() /= 0) return
|
|
|
|
info=psb_success_
|
|
|
|
info=psb_success_
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
|
|
|
|
|
|
|
|
amax=0.d0
|
|
|
|
|
|
|
|
ictxt=desc_a%get_context()
|
|
|
|
ictxt=desc_a%get_context()
|
|
|
|
|
|
|
|
|
|
|
|
call psb_info(ictxt, me, np)
|
|
|
|
call psb_info(ictxt, me, np)
|
|
|
@ -299,8 +285,7 @@ function psb_damax_vect(x, desc_a, info) result(res)
|
|
|
|
jx = 1
|
|
|
|
jx = 1
|
|
|
|
|
|
|
|
|
|
|
|
m = desc_a%get_global_rows()
|
|
|
|
m = desc_a%get_global_rows()
|
|
|
|
|
|
|
|
call psb_chkvect(m,ione,x%get_nrows(),ix,jx,desc_a,info,iix,jjx)
|
|
|
|
call psb_chkvect(m,1,x%get_nrows(),ix,jx,desc_a,info,iix,jjx)
|
|
|
|
|
|
|
|
if(info /= psb_success_) then
|
|
|
|
if(info /= psb_success_) then
|
|
|
|
info=psb_err_from_subroutine_
|
|
|
|
info=psb_err_from_subroutine_
|
|
|
|
ch_err='psb_chkvect'
|
|
|
|
ch_err='psb_chkvect'
|
|
|
@ -316,15 +301,13 @@ function psb_damax_vect(x, desc_a, info) result(res)
|
|
|
|
|
|
|
|
|
|
|
|
! compute local max
|
|
|
|
! compute local max
|
|
|
|
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
|
|
|
|
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
|
|
|
|
amax=x%amax(desc_a%get_local_rows())
|
|
|
|
res = x%amax(desc_a%get_local_rows())
|
|
|
|
else
|
|
|
|
else
|
|
|
|
amax = dzero
|
|
|
|
res = dzero
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
! compute global max
|
|
|
|
! compute global max
|
|
|
|
call psb_amx(ictxt, amax)
|
|
|
|
call psb_amx(ictxt, res)
|
|
|
|
|
|
|
|
|
|
|
|
res=amax
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
return
|
|
|
|
return
|
|
|
@ -381,35 +364,34 @@ end function psb_damax_vect
|
|
|
|
! where sub( X ) denotes X(1:N,JX:).
|
|
|
|
! where sub( X ) denotes X(1:N,JX:).
|
|
|
|
!
|
|
|
|
!
|
|
|
|
! Arguments:
|
|
|
|
! Arguments:
|
|
|
|
! res - real. The result.
|
|
|
|
! res - real The result.
|
|
|
|
! x(:,:) - real The input vector.
|
|
|
|
! x(:,:) - real The input vector.
|
|
|
|
! desc_a - type(psb_desc_type). The communication descriptor.
|
|
|
|
! desc_a - type(psb_desc_type). The communication descriptor.
|
|
|
|
! info - integer. Return code
|
|
|
|
! info - integer. Return code
|
|
|
|
! jx - integer(optional). The column offset.
|
|
|
|
! jx - integer(optional). The column offset.
|
|
|
|
!
|
|
|
|
!
|
|
|
|
subroutine psb_damaxvs (res,x,desc_a, info)
|
|
|
|
subroutine psb_damaxvs(res,x,desc_a, info)
|
|
|
|
use psb_base_mod, psb_protect_name => psb_damaxvs
|
|
|
|
use psb_base_mod, psb_protect_name => psb_damaxvs
|
|
|
|
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
|
|
|
|
real(psb_dpk_), intent(in) :: x(:)
|
|
|
|
real(psb_dpk_), intent(in) :: x(:)
|
|
|
|
type(psb_desc_type), intent(in) :: desc_a
|
|
|
|
type(psb_desc_type), intent(in) :: desc_a
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
real(psb_dpk_), intent(out) :: res
|
|
|
|
real(psb_dpk_), intent(out) :: res
|
|
|
|
|
|
|
|
|
|
|
|
! locals
|
|
|
|
! locals
|
|
|
|
integer(psb_ipk_) :: ictxt, np, me,&
|
|
|
|
integer(psb_ipk_) :: ictxt, np, me,&
|
|
|
|
& err_act, iix, jjx, ix, ijx, m, imax, idamax
|
|
|
|
& err_act, iix, jjx, ix, ijx, m, ldx
|
|
|
|
real(psb_dpk_) :: amax
|
|
|
|
character(len=20) :: name, ch_err
|
|
|
|
character(len=20) :: name, ch_err
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
name='psb_damaxvs'
|
|
|
|
name='psb_damaxvs'
|
|
|
|
if(psb_get_errstatus() /= 0) return
|
|
|
|
if(psb_get_errstatus() /= 0) return
|
|
|
|
info=psb_success_
|
|
|
|
info=psb_success_
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
|
|
|
|
|
|
|
|
amax=0.d0
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
ictxt=desc_a%get_context()
|
|
|
|
ictxt = desc_a%get_context()
|
|
|
|
|
|
|
|
|
|
|
|
call psb_info(ictxt, me, np)
|
|
|
|
call psb_info(ictxt, me, np)
|
|
|
|
if (np == -1) then
|
|
|
|
if (np == -1) then
|
|
|
@ -422,33 +404,30 @@ subroutine psb_damaxvs (res,x,desc_a, info)
|
|
|
|
ijx=1
|
|
|
|
ijx=1
|
|
|
|
|
|
|
|
|
|
|
|
m = desc_a%get_global_rows()
|
|
|
|
m = desc_a%get_global_rows()
|
|
|
|
|
|
|
|
ldx=size(x,1)
|
|
|
|
call psb_chkvect(m,1,size(x,1),ix,ijx,desc_a,info,iix,jjx)
|
|
|
|
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
|
|
|
|
if(info /= psb_success_) then
|
|
|
|
if(info /= psb_success_) then
|
|
|
|
info=psb_err_from_subroutine_
|
|
|
|
info=psb_err_from_subroutine_
|
|
|
|
ch_err='psb_chkvect'
|
|
|
|
ch_err='psb_chkvect'
|
|
|
|
call psb_errpush(info,name,a_err=ch_err)
|
|
|
|
call psb_errpush(info,name,a_err=ch_err)
|
|
|
|
goto 9999
|
|
|
|
goto 9999
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
if (iix /= 1) then
|
|
|
|
if (iix /= 1) then
|
|
|
|
info=psb_err_ix_n1_iy_n1_unsupported_
|
|
|
|
info=psb_err_ix_n1_iy_n1_unsupported_
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
call psb_errpush(info,name)
|
|
|
|
goto 9999
|
|
|
|
goto 9999
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
! compute local max
|
|
|
|
! compute local max
|
|
|
|
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
|
|
|
|
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
|
|
|
|
imax=idamax(desc_a%get_local_rows()-iix+1,x(iix),1)
|
|
|
|
res = psb_amax(desc_a%get_local_rows()-iix+1,x)
|
|
|
|
amax=abs(x(iix+imax-1))
|
|
|
|
|
|
|
|
else
|
|
|
|
else
|
|
|
|
amax = dzero
|
|
|
|
res = dzero
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
! compute global max
|
|
|
|
! compute global max
|
|
|
|
call psb_amx(ictxt, amax)
|
|
|
|
call psb_amx(ictxt, res)
|
|
|
|
|
|
|
|
|
|
|
|
res = amax
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
return
|
|
|
|
return
|
|
|
@ -457,8 +436,8 @@ subroutine psb_damaxvs (res,x,desc_a, info)
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
|
|
|
|
|
|
|
|
if (err_act == psb_act_abort_) then
|
|
|
|
if (err_act == psb_act_abort_) then
|
|
|
|
call psb_error(ictxt)
|
|
|
|
call psb_error(ictxt)
|
|
|
|
return
|
|
|
|
return
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
return
|
|
|
|
return
|
|
|
|
end subroutine psb_damaxvs
|
|
|
|
end subroutine psb_damaxvs
|
|
|
@ -502,34 +481,32 @@ end subroutine psb_damaxvs
|
|
|
|
! normi := max(abs(X(i))
|
|
|
|
! normi := max(abs(X(i))
|
|
|
|
!
|
|
|
|
!
|
|
|
|
! Arguments:
|
|
|
|
! Arguments:
|
|
|
|
! res(:) - real The result.
|
|
|
|
! res(:) - real. The result.
|
|
|
|
! x(:,:) - real The input vector.
|
|
|
|
! x(:,:) - real The input vector.
|
|
|
|
! desc_a - type(psb_desc_type). The communication descriptor.
|
|
|
|
! desc_a - type(psb_desc_type). The communication descriptor.
|
|
|
|
! info - integer. Return code
|
|
|
|
! info - integer. Return code
|
|
|
|
!
|
|
|
|
!
|
|
|
|
subroutine psb_dmamaxs (res,x,desc_a, info,jx)
|
|
|
|
subroutine psb_dmamaxs(res,x,desc_a, info,jx)
|
|
|
|
use psb_base_mod, psb_protect_name => psb_dmamaxs
|
|
|
|
use psb_base_mod, psb_protect_name => psb_dmamaxs
|
|
|
|
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
|
|
|
|
real(psb_dpk_), intent(in) :: x(:,:)
|
|
|
|
real(psb_dpk_), intent(in) :: x(:,:)
|
|
|
|
type(psb_desc_type), intent(in) :: desc_a
|
|
|
|
type(psb_desc_type), intent(in) :: desc_a
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
integer(psb_ipk_), optional, intent(in) :: jx
|
|
|
|
integer(psb_ipk_), optional, intent(in) :: jx
|
|
|
|
real(psb_dpk_), intent(out) :: res(:)
|
|
|
|
real(psb_dpk_), intent(out) :: res(:)
|
|
|
|
|
|
|
|
|
|
|
|
! locals
|
|
|
|
! locals
|
|
|
|
integer(psb_ipk_) :: ictxt, np, me,&
|
|
|
|
integer(psb_ipk_) :: ictxt, np, me,&
|
|
|
|
& err_act, iix, jjx, ix, ijx, m, imax, i, k, idamax
|
|
|
|
& err_act, iix, jjx, ix, ijx, m, ldx, i, k
|
|
|
|
real(psb_dpk_) :: amax
|
|
|
|
|
|
|
|
character(len=20) :: name, ch_err
|
|
|
|
character(len=20) :: name, ch_err
|
|
|
|
|
|
|
|
|
|
|
|
name='psb_dmamaxs'
|
|
|
|
name='psb_dmamaxs'
|
|
|
|
if (psb_errstatus_fatal()) return
|
|
|
|
if (psb_get_errstatus() /= 0) return
|
|
|
|
info=psb_success_
|
|
|
|
info=psb_success_
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
|
|
|
|
|
|
|
|
amax=0.d0
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
ictxt=desc_a%get_context()
|
|
|
|
ictxt=desc_a%get_context()
|
|
|
|
|
|
|
|
|
|
|
|
call psb_info(ictxt, me, np)
|
|
|
|
call psb_info(ictxt, me, np)
|
|
|
@ -548,8 +525,8 @@ subroutine psb_dmamaxs (res,x,desc_a, info,jx)
|
|
|
|
|
|
|
|
|
|
|
|
m = desc_a%get_global_rows()
|
|
|
|
m = desc_a%get_global_rows()
|
|
|
|
k = min(size(x,2),size(res,1))
|
|
|
|
k = min(size(x,2),size(res,1))
|
|
|
|
|
|
|
|
ldx = size(x,1)
|
|
|
|
call psb_chkvect(m,1,size(x,1),ix,ijx,desc_a,info,iix,jjx)
|
|
|
|
call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx)
|
|
|
|
if(info /= psb_success_) then
|
|
|
|
if(info /= psb_success_) then
|
|
|
|
info=psb_err_from_subroutine_
|
|
|
|
info=psb_err_from_subroutine_
|
|
|
|
ch_err='psb_chkvect'
|
|
|
|
ch_err='psb_chkvect'
|
|
|
@ -563,19 +540,17 @@ subroutine psb_dmamaxs (res,x,desc_a, info,jx)
|
|
|
|
goto 9999
|
|
|
|
goto 9999
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
res(1:k) = dzero
|
|
|
|
! compute local max
|
|
|
|
! compute local max
|
|
|
|
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
|
|
|
|
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
|
|
|
|
do i=1,k
|
|
|
|
do i=1,k
|
|
|
|
imax=idamax(desc_a%get_local_rows()-iix+1,x(iix,jjx+i-1),1)
|
|
|
|
res(i) = psb_amax(desc_a%get_local_rows()-iix+1,x(:,jjx+i-1))
|
|
|
|
res(i)=abs(x(iix+imax-1,jjx+i-1))
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
|
|
|
|
else
|
|
|
|
|
|
|
|
amax = dzero
|
|
|
|
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
! compute global max
|
|
|
|
! compute global max
|
|
|
|
call psb_amx(ictxt, res(1:k))
|
|
|
|
call psb_amx(ictxt, res(1:k))
|
|
|
|
|
|
|
|
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
return
|
|
|
|
return
|
|
|
|
|
|
|
|
|
|
|
|