Added minimum of realtype distributed vectors

merge-paraggr-newops
Cirdans-Home 5 years ago
parent 601b56f189
commit 0edb671d21

@ -183,6 +183,7 @@ module psb_c_psblas_mod
end subroutine psb_cmamaxs
end interface
interface psb_geasum
function psb_casum_vect(x, desc_a, info,global) result(res)
import :: psb_desc_type, psb_spk_, psb_ipk_, &

@ -183,6 +183,18 @@ module psb_d_psblas_mod
end subroutine psb_dmamaxs
end interface
interface psb_gemin
function psb_dmin_vect(x, desc_a, info,global) result(res)
import :: psb_desc_type, psb_dpk_, psb_ipk_, &
& psb_d_vect_type, psb_dspmat_type
real(psb_dpk_) :: res
type(psb_d_vect_type), intent (inout) :: x
type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: global
end function psb_dmin_vect
end interface
interface psb_geasum
function psb_dasum_vect(x, desc_a, info,global) result(res)
import :: psb_desc_type, psb_dpk_, psb_ipk_, &

@ -183,6 +183,18 @@ module psb_s_psblas_mod
end subroutine psb_smamaxs
end interface
interface psb_gemin
function psb_smin_vect(x, desc_a, info,global) result(res)
import :: psb_desc_type, psb_spk_, psb_ipk_, &
& psb_s_vect_type, psb_sspmat_type
real(psb_spk_) :: res
type(psb_s_vect_type), intent (inout) :: x
type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: global
end function psb_smin_vect
end interface
interface psb_geasum
function psb_sasum_vect(x, desc_a, info,global) result(res)
import :: psb_desc_type, psb_spk_, psb_ipk_, &

@ -183,6 +183,7 @@ module psb_z_psblas_mod
end subroutine psb_zmamaxs
end interface
interface psb_geasum
function psb_zasum_vect(x, desc_a, info,global) result(res)
import :: psb_desc_type, psb_dpk_, psb_ipk_, &

@ -1519,6 +1519,7 @@ contains
end function c_base_amax
!
!> Function base_asum
!! \memberof psb_c_base_vect_type

@ -988,6 +988,7 @@ contains
end function c_vect_amax
function c_vect_asum(n,x) result(res)
implicit none
class(psb_c_vect_type), intent(inout) :: x

@ -194,6 +194,7 @@ module psb_d_base_vect_mod
procedure, pass(z) :: acmp_v2 => d_base_acmp_v2
generic, public :: acmp => acmp_a2,acmp_v2
procedure, pass(x) :: minreal => d_base_min
procedure, pass(m) :: mask_v => d_base_mask_v
procedure, pass(m) :: mask_a => d_base_mask_a
generic, public :: mask => mask_a, mask_v
@ -1522,6 +1523,22 @@ contains
end function d_base_amax
!
!> Function base_min
!! \memberof psb_d_base_vect_type
!! \brief min x(1:n)
!! \param n how many entries to consider
function d_base_min(n,x) result(res)
implicit none
class(psb_d_base_vect_type), intent(inout) :: x
integer(psb_ipk_), intent(in) :: n
real(psb_dpk_) :: res
if (x%is_dev()) call x%sync()
res = minval(x%v(1:n))
end function d_base_min
!
!> Function base_asum
!! \memberof psb_d_base_vect_type

@ -118,6 +118,7 @@ module psb_d_vect_mod
procedure, pass(z) :: acmp_v2 => d_vect_acmp_v2
generic, public :: acmp => acmp_a2, acmp_v2
procedure, pass(x) :: minreal => d_vect_min
procedure, pass(m) :: mask_v => d_vect_mask_v
procedure, pass(m) :: mask_a => d_vect_mask_a
generic, public :: mask => mask_a, mask_v
@ -991,6 +992,20 @@ contains
end function d_vect_amax
function d_vect_min(n,x) result(res)
implicit none
class(psb_d_vect_type), intent(inout) :: x
integer(psb_ipk_), intent(in) :: n
real(psb_dpk_) :: res
if (allocated(x%v)) then
res = x%v%minreal(n)
else
res = dzero
end if
end function d_vect_min
function d_vect_asum(n,x) result(res)
implicit none
class(psb_d_vect_type), intent(inout) :: x

@ -194,6 +194,7 @@ module psb_s_base_vect_mod
procedure, pass(z) :: acmp_v2 => s_base_acmp_v2
generic, public :: acmp => acmp_a2,acmp_v2
procedure, pass(x) :: minreal => s_base_min
procedure, pass(m) :: mask_v => s_base_mask_v
procedure, pass(m) :: mask_a => s_base_mask_a
generic, public :: mask => mask_a, mask_v
@ -1522,6 +1523,22 @@ contains
end function s_base_amax
!
!> Function base_min
!! \memberof psb_s_base_vect_type
!! \brief min x(1:n)
!! \param n how many entries to consider
function s_base_min(n,x) result(res)
implicit none
class(psb_s_base_vect_type), intent(inout) :: x
integer(psb_ipk_), intent(in) :: n
real(psb_spk_) :: res
if (x%is_dev()) call x%sync()
res = minval(x%v(1:n))
end function s_base_min
!
!> Function base_asum
!! \memberof psb_s_base_vect_type

@ -118,6 +118,7 @@ module psb_s_vect_mod
procedure, pass(z) :: acmp_v2 => s_vect_acmp_v2
generic, public :: acmp => acmp_a2, acmp_v2
procedure, pass(x) :: minreal => s_vect_min
procedure, pass(m) :: mask_v => s_vect_mask_v
procedure, pass(m) :: mask_a => s_vect_mask_a
generic, public :: mask => mask_a, mask_v
@ -991,6 +992,20 @@ contains
end function s_vect_amax
function s_vect_min(n,x) result(res)
implicit none
class(psb_s_vect_type), intent(inout) :: x
integer(psb_ipk_), intent(in) :: n
real(psb_spk_) :: res
if (allocated(x%v)) then
res = x%v%minreal(n)
else
res = szero
end if
end function s_vect_min
function s_vect_asum(n,x) result(res)
implicit none
class(psb_s_vect_type), intent(inout) :: x

@ -1519,6 +1519,7 @@ contains
end function z_base_amax
!
!> Function base_asum
!! \memberof psb_z_base_vect_type

@ -988,6 +988,7 @@ contains
end function z_vect_amax
function z_vect_asum(n,x) result(res)
implicit none
class(psb_z_vect_type), intent(inout) :: x

@ -1,9 +1,9 @@
!
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! Salvatore Filippone
! Alfredo Buttari
!
! Salvatore Filippone
! Alfredo Buttari
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
@ -15,7 +15,7 @@
! 3. The name of the PSBLAS group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -27,14 +27,14 @@
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
!
!
! File: psb_camax.f90
!
! Function: psb_camax
! Computes the maximum absolute value of X
!
! normi := max(abs(sub(X)(i))
! normi := max(abs(sub(X)(i))
!
! where sub( X ) denotes X(1:N,JX:).
!
@ -77,7 +77,7 @@ function psb_camax(x,desc_a, info, jx,global) result(res)
if (np == -1) then
info = psb_err_context_error_
call psb_errpush(info,name)
goto 9999
goto 9999
endif
ix = 1
@ -113,7 +113,7 @@ function psb_camax(x,desc_a, info, jx,global) result(res)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = psb_amax(desc_a%get_local_rows()-iix+1,x(:,jjx))
else
else
res = szero
end if
@ -121,7 +121,7 @@ function psb_camax(x,desc_a, info, jx,global) result(res)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -131,12 +131,12 @@ end function psb_camax
!!$
!!$
!!$ Parallel Sparse BLAS version 3.5
!!$ (C) Copyright 2006-2018
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Alfredo Buttari
!!$
!!$ Alfredo Buttari
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
!!$ are met:
@ -148,7 +148,7 @@ end function psb_camax
!!$ 3. The name of the PSBLAS group or the names of its contributors may
!!$ not be used to endorse or promote products derived from this
!!$ software without specific written permission.
!!$
!!$
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -160,13 +160,13 @@ end function psb_camax
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!!$
!
! Function: psb_camaxv
! Computes the maximum absolute value of X.
!
! normi := max(abs(X(i))
! normi := max(abs(X(i))
!
! Arguments:
! x(:) - complex The input vector.
@ -237,7 +237,7 @@ function psb_camaxv (x,desc_a, info,global) result(res)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = psb_amax(desc_a%get_local_rows()-iix+1,x)
else
else
res = szero
end if
@ -245,7 +245,7 @@ function psb_camaxv (x,desc_a, info,global) result(res)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -256,7 +256,7 @@ end function psb_camaxv
! Function: psb_camax_vect
! Computes the maximum absolute value of X.
!
! normi := max(abs(X(i))
! normi := max(abs(X(i))
!
! Arguments:
! x - type(psb_c_vect_type) The input vector.
@ -302,7 +302,7 @@ function psb_camax_vect(x, desc_a, info,global) result(res)
goto 9999
endif
if (.not.allocated(x%v)) then
if (.not.allocated(x%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
@ -335,7 +335,7 @@ function psb_camax_vect(x, desc_a, info,global) result(res)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = x%amax(desc_a%get_local_rows())
else
else
res = szero
end if
@ -343,7 +343,7 @@ function psb_camax_vect(x, desc_a, info,global) result(res)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -352,12 +352,12 @@ function psb_camax_vect(x, desc_a, info,global) result(res)
end function psb_camax_vect
!!$
!!$
!!$ Parallel Sparse BLAS version 3.5
!!$ (C) Copyright 2006-2018
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Alfredo Buttari
!!$
!!$ Alfredo Buttari
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
!!$ are met:
@ -369,7 +369,7 @@ end function psb_camax_vect
!!$ 3. The name of the PSBLAS group or the names of its contributors may
!!$ not be used to endorse or promote products derived from this
!!$ software without specific written permission.
!!$
!!$
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -381,13 +381,13 @@ end function psb_camax_vect
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!!$
!!$
!
! Subroutine: psb_camaxvs
! Computes the maximum absolute value of X, subroutine version
!
! normi := max(abs(sub(X)(i))
! normi := max(abs(sub(X)(i))
!
! where sub( X ) denotes X(1:N).
!
@ -460,7 +460,7 @@ subroutine psb_camaxvs(res,x,desc_a, info,global)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = psb_amax(desc_a%get_local_rows()-iix+1,x)
else
else
res = szero
end if
@ -468,7 +468,7 @@ subroutine psb_camaxvs(res,x,desc_a, info,global)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -476,12 +476,12 @@ subroutine psb_camaxvs(res,x,desc_a, info,global)
end subroutine psb_camaxvs
!!$
!!$
!!$ Parallel Sparse BLAS version 3.5
!!$ (C) Copyright 2006-2018
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Alfredo Buttari
!!$
!!$ Alfredo Buttari
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
!!$ are met:
@ -493,7 +493,7 @@ end subroutine psb_camaxvs
!!$ 3. The name of the PSBLAS group or the names of its contributors may
!!$ not be used to endorse or promote products derived from this
!!$ software without specific written permission.
!!$
!!$
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -505,13 +505,13 @@ end subroutine psb_camaxvs
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!!$
!!$
!
! Subroutine: psb_cmamaxs
! Searches the absolute max of X.
!
! normi := max(abs(X(i))
! normi := max(abs(X(i))
!
! Arguments:
! res(:) - real. The result.
@ -596,9 +596,10 @@ subroutine psb_cmamaxs(res,x,desc_a, info,jx,global)
if (global_) call psb_amx(ictxt, res(1:k))
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_cmamaxs

@ -1,9 +1,9 @@
!
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! Salvatore Filippone
! Alfredo Buttari
!
! Salvatore Filippone
! Alfredo Buttari
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
@ -15,7 +15,7 @@
! 3. The name of the PSBLAS group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -27,14 +27,14 @@
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
!
!
! File: psb_damax.f90
!
! Function: psb_damax
! Computes the maximum absolute value of X
!
! normi := max(abs(sub(X)(i))
! normi := max(abs(sub(X)(i))
!
! where sub( X ) denotes X(1:N,JX:).
!
@ -77,7 +77,7 @@ function psb_damax(x,desc_a, info, jx,global) result(res)
if (np == -1) then
info = psb_err_context_error_
call psb_errpush(info,name)
goto 9999
goto 9999
endif
ix = 1
@ -113,7 +113,7 @@ function psb_damax(x,desc_a, info, jx,global) result(res)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = psb_amax(desc_a%get_local_rows()-iix+1,x(:,jjx))
else
else
res = dzero
end if
@ -121,7 +121,7 @@ function psb_damax(x,desc_a, info, jx,global) result(res)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -131,12 +131,12 @@ end function psb_damax
!!$
!!$
!!$ Parallel Sparse BLAS version 3.5
!!$ (C) Copyright 2006-2018
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Alfredo Buttari
!!$
!!$ Alfredo Buttari
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
!!$ are met:
@ -148,7 +148,7 @@ end function psb_damax
!!$ 3. The name of the PSBLAS group or the names of its contributors may
!!$ not be used to endorse or promote products derived from this
!!$ software without specific written permission.
!!$
!!$
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -160,13 +160,13 @@ end function psb_damax
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!!$
!
! Function: psb_damaxv
! Computes the maximum absolute value of X.
!
! normi := max(abs(X(i))
! normi := max(abs(X(i))
!
! Arguments:
! x(:) - real The input vector.
@ -237,7 +237,7 @@ function psb_damaxv (x,desc_a, info,global) result(res)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = psb_amax(desc_a%get_local_rows()-iix+1,x)
else
else
res = dzero
end if
@ -245,7 +245,7 @@ function psb_damaxv (x,desc_a, info,global) result(res)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -256,7 +256,7 @@ end function psb_damaxv
! Function: psb_damax_vect
! Computes the maximum absolute value of X.
!
! normi := max(abs(X(i))
! normi := max(abs(X(i))
!
! Arguments:
! x - type(psb_d_vect_type) The input vector.
@ -302,7 +302,7 @@ function psb_damax_vect(x, desc_a, info,global) result(res)
goto 9999
endif
if (.not.allocated(x%v)) then
if (.not.allocated(x%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
@ -335,7 +335,7 @@ function psb_damax_vect(x, desc_a, info,global) result(res)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = x%amax(desc_a%get_local_rows())
else
else
res = dzero
end if
@ -343,7 +343,7 @@ function psb_damax_vect(x, desc_a, info,global) result(res)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -352,12 +352,12 @@ function psb_damax_vect(x, desc_a, info,global) result(res)
end function psb_damax_vect
!!$
!!$
!!$ Parallel Sparse BLAS version 3.5
!!$ (C) Copyright 2006-2018
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Alfredo Buttari
!!$
!!$ Alfredo Buttari
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
!!$ are met:
@ -369,7 +369,7 @@ end function psb_damax_vect
!!$ 3. The name of the PSBLAS group or the names of its contributors may
!!$ not be used to endorse or promote products derived from this
!!$ software without specific written permission.
!!$
!!$
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -381,13 +381,13 @@ end function psb_damax_vect
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!!$
!!$
!
! Subroutine: psb_damaxvs
! Computes the maximum absolute value of X, subroutine version
!
! normi := max(abs(sub(X)(i))
! normi := max(abs(sub(X)(i))
!
! where sub( X ) denotes X(1:N).
!
@ -460,7 +460,7 @@ subroutine psb_damaxvs(res,x,desc_a, info,global)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = psb_amax(desc_a%get_local_rows()-iix+1,x)
else
else
res = dzero
end if
@ -468,7 +468,7 @@ subroutine psb_damaxvs(res,x,desc_a, info,global)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -476,12 +476,12 @@ subroutine psb_damaxvs(res,x,desc_a, info,global)
end subroutine psb_damaxvs
!!$
!!$
!!$ Parallel Sparse BLAS version 3.5
!!$ (C) Copyright 2006-2018
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Alfredo Buttari
!!$
!!$ Alfredo Buttari
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
!!$ are met:
@ -493,7 +493,7 @@ end subroutine psb_damaxvs
!!$ 3. The name of the PSBLAS group or the names of its contributors may
!!$ not be used to endorse or promote products derived from this
!!$ software without specific written permission.
!!$
!!$
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -505,13 +505,13 @@ end subroutine psb_damaxvs
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!!$
!!$
!
! Subroutine: psb_dmamaxs
! Searches the absolute max of X.
!
! normi := max(abs(X(i))
! normi := max(abs(X(i))
!
! Arguments:
! res(:) - real. The result.
@ -596,9 +596,108 @@ subroutine psb_dmamaxs(res,x,desc_a, info,jx,global)
if (global_) call psb_amx(ictxt, res(1:k))
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_dmamaxs
!
! Function: psb_dmin_vect
! Computes the minimum value of X.
!
! mini := min(X(i))
!
! Arguments:
! x - type(psb_d_vect_type) The input vector.
! desc_a - type(psb_desc_type). The communication descriptor.
! info - integer. Return code
!
function psb_dmin_vect(x, desc_a, info,global) result(res)
use psb_penv_mod
use psb_serial_mod
use psb_desc_mod
use psb_check_mod
use psb_error_mod
use psb_d_vect_mod
implicit none
real(psb_dpk_) :: res
type(psb_d_vect_type), intent (inout) :: x
type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: global
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, iix, jjx
integer(psb_lpk_) :: ix, jx, iy, ijy, m
logical :: global_
character(len=20) :: name, ch_err
name='psb_dmin_vect'
info=psb_success_
call psb_erractionsave(err_act)
if (psb_errstatus_fatal()) then
info = psb_err_internal_error_ ; goto 9999
end if
ictxt=desc_a%get_context()
call psb_info(ictxt, me, np)
if (np == -1) then
info = psb_err_context_error_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(x%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
if (present(global)) then
global_ = global
else
global_ = .true.
end if
ix = 1
jx = 1
m = desc_a%get_global_rows()
call psb_chkvect(m,lone,x%get_nrows(),ix,jx,desc_a,info,iix,jjx)
if(info /= psb_success_) then
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)
goto 9999
end if
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = x%minreal(desc_a%get_local_rows())
else
res = dzero
end if
! compute global min
if (global_) call psb_min(ictxt, res)
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end function psb_dmin_vect

@ -1,9 +1,9 @@
!
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! Salvatore Filippone
! Alfredo Buttari
!
! Salvatore Filippone
! Alfredo Buttari
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
@ -15,7 +15,7 @@
! 3. The name of the PSBLAS group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -27,14 +27,14 @@
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
!
!
! File: psb_samax.f90
!
! Function: psb_samax
! Computes the maximum absolute value of X
!
! normi := max(abs(sub(X)(i))
! normi := max(abs(sub(X)(i))
!
! where sub( X ) denotes X(1:N,JX:).
!
@ -77,7 +77,7 @@ function psb_samax(x,desc_a, info, jx,global) result(res)
if (np == -1) then
info = psb_err_context_error_
call psb_errpush(info,name)
goto 9999
goto 9999
endif
ix = 1
@ -113,7 +113,7 @@ function psb_samax(x,desc_a, info, jx,global) result(res)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = psb_amax(desc_a%get_local_rows()-iix+1,x(:,jjx))
else
else
res = szero
end if
@ -121,7 +121,7 @@ function psb_samax(x,desc_a, info, jx,global) result(res)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -131,12 +131,12 @@ end function psb_samax
!!$
!!$
!!$ Parallel Sparse BLAS version 3.5
!!$ (C) Copyright 2006-2018
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Alfredo Buttari
!!$
!!$ Alfredo Buttari
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
!!$ are met:
@ -148,7 +148,7 @@ end function psb_samax
!!$ 3. The name of the PSBLAS group or the names of its contributors may
!!$ not be used to endorse or promote products derived from this
!!$ software without specific written permission.
!!$
!!$
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -160,13 +160,13 @@ end function psb_samax
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!!$
!
! Function: psb_samaxv
! Computes the maximum absolute value of X.
!
! normi := max(abs(X(i))
! normi := max(abs(X(i))
!
! Arguments:
! x(:) - real The input vector.
@ -237,7 +237,7 @@ function psb_samaxv (x,desc_a, info,global) result(res)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = psb_amax(desc_a%get_local_rows()-iix+1,x)
else
else
res = szero
end if
@ -245,7 +245,7 @@ function psb_samaxv (x,desc_a, info,global) result(res)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -256,7 +256,7 @@ end function psb_samaxv
! Function: psb_samax_vect
! Computes the maximum absolute value of X.
!
! normi := max(abs(X(i))
! normi := max(abs(X(i))
!
! Arguments:
! x - type(psb_s_vect_type) The input vector.
@ -302,7 +302,7 @@ function psb_samax_vect(x, desc_a, info,global) result(res)
goto 9999
endif
if (.not.allocated(x%v)) then
if (.not.allocated(x%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
@ -335,7 +335,7 @@ function psb_samax_vect(x, desc_a, info,global) result(res)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = x%amax(desc_a%get_local_rows())
else
else
res = szero
end if
@ -343,7 +343,7 @@ function psb_samax_vect(x, desc_a, info,global) result(res)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -352,12 +352,12 @@ function psb_samax_vect(x, desc_a, info,global) result(res)
end function psb_samax_vect
!!$
!!$
!!$ Parallel Sparse BLAS version 3.5
!!$ (C) Copyright 2006-2018
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Alfredo Buttari
!!$
!!$ Alfredo Buttari
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
!!$ are met:
@ -369,7 +369,7 @@ end function psb_samax_vect
!!$ 3. The name of the PSBLAS group or the names of its contributors may
!!$ not be used to endorse or promote products derived from this
!!$ software without specific written permission.
!!$
!!$
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -381,13 +381,13 @@ end function psb_samax_vect
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!!$
!!$
!
! Subroutine: psb_samaxvs
! Computes the maximum absolute value of X, subroutine version
!
! normi := max(abs(sub(X)(i))
! normi := max(abs(sub(X)(i))
!
! where sub( X ) denotes X(1:N).
!
@ -460,7 +460,7 @@ subroutine psb_samaxvs(res,x,desc_a, info,global)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = psb_amax(desc_a%get_local_rows()-iix+1,x)
else
else
res = szero
end if
@ -468,7 +468,7 @@ subroutine psb_samaxvs(res,x,desc_a, info,global)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -476,12 +476,12 @@ subroutine psb_samaxvs(res,x,desc_a, info,global)
end subroutine psb_samaxvs
!!$
!!$
!!$ Parallel Sparse BLAS version 3.5
!!$ (C) Copyright 2006-2018
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Alfredo Buttari
!!$
!!$ Alfredo Buttari
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
!!$ are met:
@ -493,7 +493,7 @@ end subroutine psb_samaxvs
!!$ 3. The name of the PSBLAS group or the names of its contributors may
!!$ not be used to endorse or promote products derived from this
!!$ software without specific written permission.
!!$
!!$
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -505,13 +505,13 @@ end subroutine psb_samaxvs
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!!$
!!$
!
! Subroutine: psb_smamaxs
! Searches the absolute max of X.
!
! normi := max(abs(X(i))
! normi := max(abs(X(i))
!
! Arguments:
! res(:) - real. The result.
@ -596,9 +596,108 @@ subroutine psb_smamaxs(res,x,desc_a, info,jx,global)
if (global_) call psb_amx(ictxt, res(1:k))
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_smamaxs
!
! Function: psb_smin_vect
! Computes the minimum value of X.
!
! mini := min(X(i))
!
! Arguments:
! x - type(psb_s_vect_type) The input vector.
! desc_a - type(psb_desc_type). The communication descriptor.
! info - integer. Return code
!
function psb_smin_vect(x, desc_a, info,global) result(res)
use psb_penv_mod
use psb_serial_mod
use psb_desc_mod
use psb_check_mod
use psb_error_mod
use psb_s_vect_mod
implicit none
real(psb_spk_) :: res
type(psb_s_vect_type), intent (inout) :: x
type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: global
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, iix, jjx
integer(psb_lpk_) :: ix, jx, iy, ijy, m
logical :: global_
character(len=20) :: name, ch_err
name='psb_smin_vect'
info=psb_success_
call psb_erractionsave(err_act)
if (psb_errstatus_fatal()) then
info = psb_err_internal_error_ ; goto 9999
end if
ictxt=desc_a%get_context()
call psb_info(ictxt, me, np)
if (np == -1) then
info = psb_err_context_error_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(x%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
if (present(global)) then
global_ = global
else
global_ = .true.
end if
ix = 1
jx = 1
m = desc_a%get_global_rows()
call psb_chkvect(m,lone,x%get_nrows(),ix,jx,desc_a,info,iix,jjx)
if(info /= psb_success_) then
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)
goto 9999
end if
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = x%minreal(desc_a%get_local_rows())
else
res = szero
end if
! compute global min
if (global_) call psb_min(ictxt, res)
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end function psb_smin_vect

@ -1,9 +1,9 @@
!
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! Salvatore Filippone
! Alfredo Buttari
!
! Salvatore Filippone
! Alfredo Buttari
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
@ -15,7 +15,7 @@
! 3. The name of the PSBLAS group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -27,14 +27,14 @@
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
!
!
! File: psb_zamax.f90
!
! Function: psb_zamax
! Computes the maximum absolute value of X
!
! normi := max(abs(sub(X)(i))
! normi := max(abs(sub(X)(i))
!
! where sub( X ) denotes X(1:N,JX:).
!
@ -77,7 +77,7 @@ function psb_zamax(x,desc_a, info, jx,global) result(res)
if (np == -1) then
info = psb_err_context_error_
call psb_errpush(info,name)
goto 9999
goto 9999
endif
ix = 1
@ -113,7 +113,7 @@ function psb_zamax(x,desc_a, info, jx,global) result(res)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = psb_amax(desc_a%get_local_rows()-iix+1,x(:,jjx))
else
else
res = dzero
end if
@ -121,7 +121,7 @@ function psb_zamax(x,desc_a, info, jx,global) result(res)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -131,12 +131,12 @@ end function psb_zamax
!!$
!!$
!!$ Parallel Sparse BLAS version 3.5
!!$ (C) Copyright 2006-2018
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Alfredo Buttari
!!$
!!$ Alfredo Buttari
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
!!$ are met:
@ -148,7 +148,7 @@ end function psb_zamax
!!$ 3. The name of the PSBLAS group or the names of its contributors may
!!$ not be used to endorse or promote products derived from this
!!$ software without specific written permission.
!!$
!!$
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -160,13 +160,13 @@ end function psb_zamax
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!!$
!
! Function: psb_zamaxv
! Computes the maximum absolute value of X.
!
! normi := max(abs(X(i))
! normi := max(abs(X(i))
!
! Arguments:
! x(:) - complex The input vector.
@ -237,7 +237,7 @@ function psb_zamaxv (x,desc_a, info,global) result(res)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = psb_amax(desc_a%get_local_rows()-iix+1,x)
else
else
res = dzero
end if
@ -245,7 +245,7 @@ function psb_zamaxv (x,desc_a, info,global) result(res)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -256,7 +256,7 @@ end function psb_zamaxv
! Function: psb_zamax_vect
! Computes the maximum absolute value of X.
!
! normi := max(abs(X(i))
! normi := max(abs(X(i))
!
! Arguments:
! x - type(psb_z_vect_type) The input vector.
@ -302,7 +302,7 @@ function psb_zamax_vect(x, desc_a, info,global) result(res)
goto 9999
endif
if (.not.allocated(x%v)) then
if (.not.allocated(x%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
@ -335,7 +335,7 @@ function psb_zamax_vect(x, desc_a, info,global) result(res)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = x%amax(desc_a%get_local_rows())
else
else
res = dzero
end if
@ -343,7 +343,7 @@ function psb_zamax_vect(x, desc_a, info,global) result(res)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -352,12 +352,12 @@ function psb_zamax_vect(x, desc_a, info,global) result(res)
end function psb_zamax_vect
!!$
!!$
!!$ Parallel Sparse BLAS version 3.5
!!$ (C) Copyright 2006-2018
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Alfredo Buttari
!!$
!!$ Alfredo Buttari
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
!!$ are met:
@ -369,7 +369,7 @@ end function psb_zamax_vect
!!$ 3. The name of the PSBLAS group or the names of its contributors may
!!$ not be used to endorse or promote products derived from this
!!$ software without specific written permission.
!!$
!!$
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -381,13 +381,13 @@ end function psb_zamax_vect
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!!$
!!$
!
! Subroutine: psb_zamaxvs
! Computes the maximum absolute value of X, subroutine version
!
! normi := max(abs(sub(X)(i))
! normi := max(abs(sub(X)(i))
!
! where sub( X ) denotes X(1:N).
!
@ -460,7 +460,7 @@ subroutine psb_zamaxvs(res,x,desc_a, info,global)
! compute local max
if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then
res = psb_amax(desc_a%get_local_rows()-iix+1,x)
else
else
res = dzero
end if
@ -468,7 +468,7 @@ subroutine psb_zamaxvs(res,x,desc_a, info,global)
if (global_) call psb_amx(ictxt, res)
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
@ -476,12 +476,12 @@ subroutine psb_zamaxvs(res,x,desc_a, info,global)
end subroutine psb_zamaxvs
!!$
!!$
!!$ Parallel Sparse BLAS version 3.5
!!$ (C) Copyright 2006-2018
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Alfredo Buttari
!!$
!!$ Alfredo Buttari
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
!!$ are met:
@ -493,7 +493,7 @@ end subroutine psb_zamaxvs
!!$ 3. The name of the PSBLAS group or the names of its contributors may
!!$ not be used to endorse or promote products derived from this
!!$ software without specific written permission.
!!$
!!$
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
@ -505,13 +505,13 @@ end subroutine psb_zamaxvs
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!!$
!!$
!
! Subroutine: psb_zmamaxs
! Searches the absolute max of X.
!
! normi := max(abs(X(i))
! normi := max(abs(X(i))
!
! Arguments:
! res(:) - real. The result.
@ -596,9 +596,10 @@ subroutine psb_zmamaxs(res,x,desc_a, info,jx,global)
if (global_) call psb_amx(ictxt, res(1:k))
call psb_erractionrestore(err_act)
return
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_zmamaxs

Loading…
Cancel
Save