chagend name to acmp for the compare routines

merge-paraggr-newops
Cirdans-Home 5 years ago
parent 87306f4d1a
commit e59932e496

@ -190,9 +190,9 @@ module psb_c_base_vect_mod
! !
! Comparison and mask operation ! Comparison and mask operation
! !
procedure, pass(z) :: cmp_a2 => c_base_cmp_a2 procedure, pass(z) :: acmp_a2 => c_base_acmp_a2
procedure, pass(z) :: cmp_v2 => c_base_cmp_v2 procedure, pass(z) :: acmp_v2 => c_base_acmp_v2
generic, public :: cmp => cmp_a2,cmp_v2 generic, public :: acmp => acmp_a2,acmp_v2
end type psb_c_base_vect_type end type psb_c_base_vect_type
@ -1418,7 +1418,7 @@ contains
!! \param c The comparison term !! \param c The comparison term
!! \param info return code !! \param info return code
! !
subroutine c_base_cmp_a2(x,c,z,info) subroutine c_base_acmp_a2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
real(psb_spk_), intent(in) :: c real(psb_spk_), intent(in) :: c
@ -1439,7 +1439,7 @@ contains
end do end do
info = 0 info = 0
end subroutine c_base_cmp_a2 end subroutine c_base_acmp_a2
! !
!> Function base_cmp_v2 !> Function base_cmp_v2
!! \memberof psb_c_base_vect_type !! \memberof psb_c_base_vect_type
@ -1449,7 +1449,7 @@ contains
!! \param c The comparison term !! \param c The comparison term
!! \param info return code !! \param info return code
! !
subroutine c_base_cmp_v2(x,c,z,info) subroutine c_base_acmp_v2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
class(psb_c_base_vect_type), intent(inout) :: x class(psb_c_base_vect_type), intent(inout) :: x
@ -1459,8 +1459,8 @@ contains
info = 0 info = 0
if (x%is_dev()) call x%sync() if (x%is_dev()) call x%sync()
call z%cmp(x%v,c,info) call z%acmp(x%v,c,info)
end subroutine c_base_cmp_v2 end subroutine c_base_acmp_v2
! !
! Simple scaling ! Simple scaling

@ -114,9 +114,9 @@ module psb_c_vect_mod
generic, public :: nrm2 => nrm2std, nrm2weight, nrm2weightmask generic, public :: nrm2 => nrm2std, nrm2weight, nrm2weightmask
procedure, pass(x) :: amax => c_vect_amax procedure, pass(x) :: amax => c_vect_amax
procedure, pass(x) :: asum => c_vect_asum procedure, pass(x) :: asum => c_vect_asum
procedure, pass(z) :: cmp_a2 => c_vect_cmp_a2 procedure, pass(z) :: acmp_a2 => c_vect_acmp_a2
procedure, pass(z) :: cmp_v2 => c_vect_cmp_v2 procedure, pass(z) :: acmp_v2 => c_vect_acmp_v2
generic, public :: cmp => cmp_a2, cmp_v2 generic, public :: acmp => acmp_a2, acmp_v2
end type psb_c_vect_type end type psb_c_vect_type
@ -144,7 +144,7 @@ module psb_c_vect_mod
! @NOTCPLXS@ ! @NOTCPLXS@
! @NOTINTS@ ! @NOTINTS@
! private :: c_vect_cmp_a2, c_vect_cmp_v2 ! private :: c_vect_acmp_a2, c_vect_acmp_v2
! @NOTINTE@ ! @NOTINTE@
! @NOTCPLXE@ ! @NOTCPLXE@
@ -867,7 +867,7 @@ contains
end subroutine c_vect_inv_a2_check end subroutine c_vect_inv_a2_check
subroutine c_vect_cmp_a2(x,c,z,info) subroutine c_vect_acmp_a2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
real(psb_spk_), intent(in) :: c real(psb_spk_), intent(in) :: c
@ -877,11 +877,11 @@ contains
info = 0 info = 0
if (allocated(z%v)) & if (allocated(z%v)) &
& call z%cmp(x,c,info) & call z%acmp(x,c,info)
end subroutine c_vect_cmp_a2 end subroutine c_vect_acmp_a2
subroutine c_vect_cmp_v2(x,c,z,info) subroutine c_vect_acmp_v2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
real(psb_spk_), intent(in) :: c real(psb_spk_), intent(in) :: c
@ -891,9 +891,9 @@ contains
info = 0 info = 0
if (allocated(x%v).and.allocated(z%v)) & if (allocated(x%v).and.allocated(z%v)) &
& call z%v%cmp(x%v,c,info) & call z%v%acmp(x%v,c,info)
end subroutine c_vect_cmp_v2 end subroutine c_vect_acmp_v2
subroutine c_vect_scal(alpha, x) subroutine c_vect_scal(alpha, x)
use psi_serial_mod use psi_serial_mod
@ -964,7 +964,7 @@ contains
integer(psb_ipk_) :: info integer(psb_ipk_) :: info
if (allocated(x%v).and.allocated(w%v).and.allocated(id%v)) then if (allocated(x%v).and.allocated(w%v).and.allocated(id%v)) then
call w%v%cmp(id%v,szero,info) call w%v%acmp(id%v,szero,info)
call w%v%mlt(x%v,info) call w%v%mlt(x%v,info)
res = w%v%nrm2(n) res = w%v%nrm2(n)
else else

@ -190,9 +190,9 @@ module psb_d_base_vect_mod
! !
! Comparison and mask operation ! Comparison and mask operation
! !
procedure, pass(z) :: cmp_a2 => d_base_cmp_a2 procedure, pass(z) :: acmp_a2 => d_base_acmp_a2
procedure, pass(z) :: cmp_v2 => d_base_cmp_v2 procedure, pass(z) :: acmp_v2 => d_base_acmp_v2
generic, public :: cmp => cmp_a2,cmp_v2 generic, public :: acmp => acmp_a2,acmp_v2
end type psb_d_base_vect_type end type psb_d_base_vect_type
@ -1418,7 +1418,7 @@ contains
!! \param c The comparison term !! \param c The comparison term
!! \param info return code !! \param info return code
! !
subroutine d_base_cmp_a2(x,c,z,info) subroutine d_base_acmp_a2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
real(psb_dpk_), intent(in) :: c real(psb_dpk_), intent(in) :: c
@ -1439,7 +1439,7 @@ contains
end do end do
info = 0 info = 0
end subroutine d_base_cmp_a2 end subroutine d_base_acmp_a2
! !
!> Function base_cmp_v2 !> Function base_cmp_v2
!! \memberof psb_d_base_vect_type !! \memberof psb_d_base_vect_type
@ -1449,7 +1449,7 @@ contains
!! \param c The comparison term !! \param c The comparison term
!! \param info return code !! \param info return code
! !
subroutine d_base_cmp_v2(x,c,z,info) subroutine d_base_acmp_v2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
class(psb_d_base_vect_type), intent(inout) :: x class(psb_d_base_vect_type), intent(inout) :: x
@ -1459,8 +1459,8 @@ contains
info = 0 info = 0
if (x%is_dev()) call x%sync() if (x%is_dev()) call x%sync()
call z%cmp(x%v,c,info) call z%acmp(x%v,c,info)
end subroutine d_base_cmp_v2 end subroutine d_base_acmp_v2
! !
! Simple scaling ! Simple scaling

@ -114,9 +114,9 @@ module psb_d_vect_mod
generic, public :: nrm2 => nrm2std, nrm2weight, nrm2weightmask generic, public :: nrm2 => nrm2std, nrm2weight, nrm2weightmask
procedure, pass(x) :: amax => d_vect_amax procedure, pass(x) :: amax => d_vect_amax
procedure, pass(x) :: asum => d_vect_asum procedure, pass(x) :: asum => d_vect_asum
procedure, pass(z) :: cmp_a2 => d_vect_cmp_a2 procedure, pass(z) :: acmp_a2 => d_vect_acmp_a2
procedure, pass(z) :: cmp_v2 => d_vect_cmp_v2 procedure, pass(z) :: acmp_v2 => d_vect_acmp_v2
generic, public :: cmp => cmp_a2, cmp_v2 generic, public :: acmp => acmp_a2, acmp_v2
end type psb_d_vect_type end type psb_d_vect_type
@ -144,7 +144,7 @@ module psb_d_vect_mod
! @NOTCPLXS@ ! @NOTCPLXS@
! @NOTINTS@ ! @NOTINTS@
! private :: d_vect_cmp_a2, d_vect_cmp_v2 ! private :: d_vect_acmp_a2, d_vect_acmp_v2
! @NOTINTE@ ! @NOTINTE@
! @NOTCPLXE@ ! @NOTCPLXE@
@ -867,7 +867,7 @@ contains
end subroutine d_vect_inv_a2_check end subroutine d_vect_inv_a2_check
subroutine d_vect_cmp_a2(x,c,z,info) subroutine d_vect_acmp_a2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
real(psb_dpk_), intent(in) :: c real(psb_dpk_), intent(in) :: c
@ -877,11 +877,11 @@ contains
info = 0 info = 0
if (allocated(z%v)) & if (allocated(z%v)) &
& call z%cmp(x,c,info) & call z%acmp(x,c,info)
end subroutine d_vect_cmp_a2 end subroutine d_vect_acmp_a2
subroutine d_vect_cmp_v2(x,c,z,info) subroutine d_vect_acmp_v2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
real(psb_dpk_), intent(in) :: c real(psb_dpk_), intent(in) :: c
@ -891,9 +891,9 @@ contains
info = 0 info = 0
if (allocated(x%v).and.allocated(z%v)) & if (allocated(x%v).and.allocated(z%v)) &
& call z%v%cmp(x%v,c,info) & call z%v%acmp(x%v,c,info)
end subroutine d_vect_cmp_v2 end subroutine d_vect_acmp_v2
subroutine d_vect_scal(alpha, x) subroutine d_vect_scal(alpha, x)
use psi_serial_mod use psi_serial_mod
@ -964,7 +964,7 @@ contains
integer(psb_ipk_) :: info integer(psb_ipk_) :: info
if (allocated(x%v).and.allocated(w%v).and.allocated(id%v)) then if (allocated(x%v).and.allocated(w%v).and.allocated(id%v)) then
call w%v%cmp(id%v,dzero,info) call w%v%acmp(id%v,dzero,info)
call w%v%mlt(x%v,info) call w%v%mlt(x%v,info)
res = w%v%nrm2(n) res = w%v%nrm2(n)
else else

@ -101,7 +101,7 @@ module psb_i_vect_mod
! @NOTCPLXS@ ! @NOTCPLXS@
! @NOTINTS@ ! @NOTINTS@
! private :: i_vect_cmp_a2, i_vect_cmp_v2 ! private :: i_vect_acmp_a2, i_vect_acmp_v2
! @NOTINTE@ ! @NOTINTE@
! @NOTCPLXE@ ! @NOTCPLXE@

@ -102,7 +102,7 @@ module psb_l_vect_mod
! @NOTCPLXS@ ! @NOTCPLXS@
! @NOTINTS@ ! @NOTINTS@
! private :: l_vect_cmp_a2, l_vect_cmp_v2 ! private :: l_vect_acmp_a2, l_vect_acmp_v2
! @NOTINTE@ ! @NOTINTE@
! @NOTCPLXE@ ! @NOTCPLXE@

@ -190,9 +190,9 @@ module psb_s_base_vect_mod
! !
! Comparison and mask operation ! Comparison and mask operation
! !
procedure, pass(z) :: cmp_a2 => s_base_cmp_a2 procedure, pass(z) :: acmp_a2 => s_base_acmp_a2
procedure, pass(z) :: cmp_v2 => s_base_cmp_v2 procedure, pass(z) :: acmp_v2 => s_base_acmp_v2
generic, public :: cmp => cmp_a2,cmp_v2 generic, public :: acmp => acmp_a2,acmp_v2
end type psb_s_base_vect_type end type psb_s_base_vect_type
@ -1418,7 +1418,7 @@ contains
!! \param c The comparison term !! \param c The comparison term
!! \param info return code !! \param info return code
! !
subroutine s_base_cmp_a2(x,c,z,info) subroutine s_base_acmp_a2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
real(psb_spk_), intent(in) :: c real(psb_spk_), intent(in) :: c
@ -1439,7 +1439,7 @@ contains
end do end do
info = 0 info = 0
end subroutine s_base_cmp_a2 end subroutine s_base_acmp_a2
! !
!> Function base_cmp_v2 !> Function base_cmp_v2
!! \memberof psb_s_base_vect_type !! \memberof psb_s_base_vect_type
@ -1449,7 +1449,7 @@ contains
!! \param c The comparison term !! \param c The comparison term
!! \param info return code !! \param info return code
! !
subroutine s_base_cmp_v2(x,c,z,info) subroutine s_base_acmp_v2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
class(psb_s_base_vect_type), intent(inout) :: x class(psb_s_base_vect_type), intent(inout) :: x
@ -1459,8 +1459,8 @@ contains
info = 0 info = 0
if (x%is_dev()) call x%sync() if (x%is_dev()) call x%sync()
call z%cmp(x%v,c,info) call z%acmp(x%v,c,info)
end subroutine s_base_cmp_v2 end subroutine s_base_acmp_v2
! !
! Simple scaling ! Simple scaling

@ -114,9 +114,9 @@ module psb_s_vect_mod
generic, public :: nrm2 => nrm2std, nrm2weight, nrm2weightmask generic, public :: nrm2 => nrm2std, nrm2weight, nrm2weightmask
procedure, pass(x) :: amax => s_vect_amax procedure, pass(x) :: amax => s_vect_amax
procedure, pass(x) :: asum => s_vect_asum procedure, pass(x) :: asum => s_vect_asum
procedure, pass(z) :: cmp_a2 => s_vect_cmp_a2 procedure, pass(z) :: acmp_a2 => s_vect_acmp_a2
procedure, pass(z) :: cmp_v2 => s_vect_cmp_v2 procedure, pass(z) :: acmp_v2 => s_vect_acmp_v2
generic, public :: cmp => cmp_a2, cmp_v2 generic, public :: acmp => acmp_a2, acmp_v2
end type psb_s_vect_type end type psb_s_vect_type
@ -144,7 +144,7 @@ module psb_s_vect_mod
! @NOTCPLXS@ ! @NOTCPLXS@
! @NOTINTS@ ! @NOTINTS@
! private :: s_vect_cmp_a2, s_vect_cmp_v2 ! private :: s_vect_acmp_a2, s_vect_acmp_v2
! @NOTINTE@ ! @NOTINTE@
! @NOTCPLXE@ ! @NOTCPLXE@
@ -867,7 +867,7 @@ contains
end subroutine s_vect_inv_a2_check end subroutine s_vect_inv_a2_check
subroutine s_vect_cmp_a2(x,c,z,info) subroutine s_vect_acmp_a2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
real(psb_spk_), intent(in) :: c real(psb_spk_), intent(in) :: c
@ -877,11 +877,11 @@ contains
info = 0 info = 0
if (allocated(z%v)) & if (allocated(z%v)) &
& call z%cmp(x,c,info) & call z%acmp(x,c,info)
end subroutine s_vect_cmp_a2 end subroutine s_vect_acmp_a2
subroutine s_vect_cmp_v2(x,c,z,info) subroutine s_vect_acmp_v2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
real(psb_spk_), intent(in) :: c real(psb_spk_), intent(in) :: c
@ -891,9 +891,9 @@ contains
info = 0 info = 0
if (allocated(x%v).and.allocated(z%v)) & if (allocated(x%v).and.allocated(z%v)) &
& call z%v%cmp(x%v,c,info) & call z%v%acmp(x%v,c,info)
end subroutine s_vect_cmp_v2 end subroutine s_vect_acmp_v2
subroutine s_vect_scal(alpha, x) subroutine s_vect_scal(alpha, x)
use psi_serial_mod use psi_serial_mod
@ -964,7 +964,7 @@ contains
integer(psb_ipk_) :: info integer(psb_ipk_) :: info
if (allocated(x%v).and.allocated(w%v).and.allocated(id%v)) then if (allocated(x%v).and.allocated(w%v).and.allocated(id%v)) then
call w%v%cmp(id%v,szero,info) call w%v%acmp(id%v,szero,info)
call w%v%mlt(x%v,info) call w%v%mlt(x%v,info)
res = w%v%nrm2(n) res = w%v%nrm2(n)
else else

@ -190,9 +190,9 @@ module psb_z_base_vect_mod
! !
! Comparison and mask operation ! Comparison and mask operation
! !
procedure, pass(z) :: cmp_a2 => z_base_cmp_a2 procedure, pass(z) :: acmp_a2 => z_base_acmp_a2
procedure, pass(z) :: cmp_v2 => z_base_cmp_v2 procedure, pass(z) :: acmp_v2 => z_base_acmp_v2
generic, public :: cmp => cmp_a2,cmp_v2 generic, public :: acmp => acmp_a2,acmp_v2
end type psb_z_base_vect_type end type psb_z_base_vect_type
@ -1418,7 +1418,7 @@ contains
!! \param c The comparison term !! \param c The comparison term
!! \param info return code !! \param info return code
! !
subroutine z_base_cmp_a2(x,c,z,info) subroutine z_base_acmp_a2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
real(psb_dpk_), intent(in) :: c real(psb_dpk_), intent(in) :: c
@ -1439,7 +1439,7 @@ contains
end do end do
info = 0 info = 0
end subroutine z_base_cmp_a2 end subroutine z_base_acmp_a2
! !
!> Function base_cmp_v2 !> Function base_cmp_v2
!! \memberof psb_z_base_vect_type !! \memberof psb_z_base_vect_type
@ -1449,7 +1449,7 @@ contains
!! \param c The comparison term !! \param c The comparison term
!! \param info return code !! \param info return code
! !
subroutine z_base_cmp_v2(x,c,z,info) subroutine z_base_acmp_v2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
class(psb_z_base_vect_type), intent(inout) :: x class(psb_z_base_vect_type), intent(inout) :: x
@ -1459,8 +1459,8 @@ contains
info = 0 info = 0
if (x%is_dev()) call x%sync() if (x%is_dev()) call x%sync()
call z%cmp(x%v,c,info) call z%acmp(x%v,c,info)
end subroutine z_base_cmp_v2 end subroutine z_base_acmp_v2
! !
! Simple scaling ! Simple scaling

@ -114,9 +114,9 @@ module psb_z_vect_mod
generic, public :: nrm2 => nrm2std, nrm2weight, nrm2weightmask generic, public :: nrm2 => nrm2std, nrm2weight, nrm2weightmask
procedure, pass(x) :: amax => z_vect_amax procedure, pass(x) :: amax => z_vect_amax
procedure, pass(x) :: asum => z_vect_asum procedure, pass(x) :: asum => z_vect_asum
procedure, pass(z) :: cmp_a2 => z_vect_cmp_a2 procedure, pass(z) :: acmp_a2 => z_vect_acmp_a2
procedure, pass(z) :: cmp_v2 => z_vect_cmp_v2 procedure, pass(z) :: acmp_v2 => z_vect_acmp_v2
generic, public :: cmp => cmp_a2, cmp_v2 generic, public :: acmp => acmp_a2, acmp_v2
end type psb_z_vect_type end type psb_z_vect_type
@ -144,7 +144,7 @@ module psb_z_vect_mod
! @NOTCPLXS@ ! @NOTCPLXS@
! @NOTINTS@ ! @NOTINTS@
! private :: z_vect_cmp_a2, z_vect_cmp_v2 ! private :: z_vect_acmp_a2, z_vect_acmp_v2
! @NOTINTE@ ! @NOTINTE@
! @NOTCPLXE@ ! @NOTCPLXE@
@ -867,7 +867,7 @@ contains
end subroutine z_vect_inv_a2_check end subroutine z_vect_inv_a2_check
subroutine z_vect_cmp_a2(x,c,z,info) subroutine z_vect_acmp_a2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
real(psb_dpk_), intent(in) :: c real(psb_dpk_), intent(in) :: c
@ -877,11 +877,11 @@ contains
info = 0 info = 0
if (allocated(z%v)) & if (allocated(z%v)) &
& call z%cmp(x,c,info) & call z%acmp(x,c,info)
end subroutine z_vect_cmp_a2 end subroutine z_vect_acmp_a2
subroutine z_vect_cmp_v2(x,c,z,info) subroutine z_vect_acmp_v2(x,c,z,info)
use psi_serial_mod use psi_serial_mod
implicit none implicit none
real(psb_dpk_), intent(in) :: c real(psb_dpk_), intent(in) :: c
@ -891,9 +891,9 @@ contains
info = 0 info = 0
if (allocated(x%v).and.allocated(z%v)) & if (allocated(x%v).and.allocated(z%v)) &
& call z%v%cmp(x%v,c,info) & call z%v%acmp(x%v,c,info)
end subroutine z_vect_cmp_v2 end subroutine z_vect_acmp_v2
subroutine z_vect_scal(alpha, x) subroutine z_vect_scal(alpha, x)
use psi_serial_mod use psi_serial_mod
@ -964,7 +964,7 @@ contains
integer(psb_ipk_) :: info integer(psb_ipk_) :: info
if (allocated(x%v).and.allocated(w%v).and.allocated(id%v)) then if (allocated(x%v).and.allocated(w%v).and.allocated(id%v)) then
call w%v%cmp(id%v,dzero,info) call w%v%acmp(id%v,dzero,info)
call w%v%mlt(x%v,info) call w%v%mlt(x%v,info)
res = w%v%nrm2(n) res = w%v%nrm2(n)
else else

@ -92,7 +92,7 @@ subroutine psb_ccmp_vect(x,c,z,desc_a,info)
end if end if
if(desc_a%get_local_rows() > 0) then if(desc_a%get_local_rows() > 0) then
call z%cmp(x,c,info) call z%acmp(x,c,info)
end if end if
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)

@ -92,7 +92,7 @@ subroutine psb_dcmp_vect(x,c,z,desc_a,info)
end if end if
if(desc_a%get_local_rows() > 0) then if(desc_a%get_local_rows() > 0) then
call z%cmp(x,c,info) call z%acmp(x,c,info)
end if end if
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)

@ -92,7 +92,7 @@ subroutine psb_scmp_vect(x,c,z,desc_a,info)
end if end if
if(desc_a%get_local_rows() > 0) then if(desc_a%get_local_rows() > 0) then
call z%cmp(x,c,info) call z%acmp(x,c,info)
end if end if
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)

@ -92,7 +92,7 @@ subroutine psb_zcmp_vect(x,c,z,desc_a,info)
end if end if
if(desc_a%get_local_rows() > 0) then if(desc_a%get_local_rows() > 0) then
call z%cmp(x,c,info) call z%acmp(x,c,info)
end if end if
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)

Loading…
Cancel
Save