More interface mismatch fixes

remap-coarse
Salvatore Filippone 4 years ago
parent 340c191e7f
commit 1c98111fd9

@ -71,7 +71,7 @@ subroutine psi_adjcncy_fnd_owner(idx,iprc,adj,idxmap,info)
#endif
integer(psb_lpk_), intent(in) :: idx(:)
integer(psb_ipk_), allocatable, intent(out) :: iprc(:)
integer(psb_ipk_), intent(in) :: adj(:)
integer(psb_ipk_), intent(inout) :: adj(:)
class(psb_indx_map), intent(in) :: idxmap
integer(psb_ipk_), intent(out) :: info

@ -84,7 +84,8 @@ subroutine psi_i_csr_sort_dl(dl_ptr,c_dep_list,l_dep_list,ctxt,info)
use psb_sort_mod
implicit none
integer(psb_ipk_), intent(inout) :: c_dep_list(:), dl_ptr(0:), l_dep_list(0:)
integer(psb_ipk_), intent(in) :: dl_ptr(0:)
integer(psb_ipk_), intent(inout) :: c_dep_list(:), l_dep_list(0:)
type(psb_ctxt_type), intent(in) :: ctxt
integer(psb_ipk_), intent(out) :: info
! Local variables

@ -45,7 +45,8 @@ module psb_c_hsort_x_mod
use psb_c_hsort_mod
type psb_c_heap
integer(psb_ipk_) :: last, dir
integer(psb_ipk_) :: dir
integer(psb_ipk_) :: last
complex(psb_spk_), allocatable :: keys(:)
contains
procedure, pass(heap) :: init => psb_c_init_heap
@ -57,7 +58,8 @@ module psb_c_hsort_x_mod
end type psb_c_heap
type psb_c_idx_heap
integer(psb_ipk_) :: last, dir
integer(psb_ipk_) :: dir
integer(psb_ipk_) :: last
complex(psb_spk_), allocatable :: keys(:)
integer(psb_ipk_), allocatable :: idxs(:)
contains
@ -121,7 +123,7 @@ contains
return
endif
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=psb_heap_resize)
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info /= psb_success_) then
write(psb_err_unit,*) 'Memory allocation failure in heap_insert'
info = -5
@ -234,9 +236,9 @@ contains
return
endif
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=psb_heap_resize)
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info == psb_success_) &
& call psb_ensure_size(heap%last+1,heap%idxs,info,addsz=psb_heap_resize)
& call psb_ensure_size(heap%last+1,heap%idxs,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info /= psb_success_) then
write(psb_err_unit,*) 'Memory allocation failure in heap_insert'
info = -5
@ -254,7 +256,7 @@ contains
class(psb_c_idx_heap), intent(inout) :: heap
integer(psb_ipk_), intent(out) :: index
integer(psb_ipk_), intent(out) :: info
complex(psb_spk_), intent(out) :: key
complex(psb_spk_), intent(inout) :: key
info = psb_success_

@ -45,7 +45,8 @@ module psb_d_hsort_x_mod
use psb_d_hsort_mod
type psb_d_heap
integer(psb_ipk_) :: last, dir
integer(psb_ipk_) :: dir
integer(psb_ipk_) :: last
real(psb_dpk_), allocatable :: keys(:)
contains
procedure, pass(heap) :: init => psb_d_init_heap
@ -57,7 +58,8 @@ module psb_d_hsort_x_mod
end type psb_d_heap
type psb_d_idx_heap
integer(psb_ipk_) :: last, dir
integer(psb_ipk_) :: dir
integer(psb_ipk_) :: last
real(psb_dpk_), allocatable :: keys(:)
integer(psb_ipk_), allocatable :: idxs(:)
contains
@ -121,7 +123,7 @@ contains
return
endif
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=psb_heap_resize)
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info /= psb_success_) then
write(psb_err_unit,*) 'Memory allocation failure in heap_insert'
info = -5
@ -234,9 +236,9 @@ contains
return
endif
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=psb_heap_resize)
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info == psb_success_) &
& call psb_ensure_size(heap%last+1,heap%idxs,info,addsz=psb_heap_resize)
& call psb_ensure_size(heap%last+1,heap%idxs,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info /= psb_success_) then
write(psb_err_unit,*) 'Memory allocation failure in heap_insert'
info = -5
@ -254,7 +256,7 @@ contains
class(psb_d_idx_heap), intent(inout) :: heap
integer(psb_ipk_), intent(out) :: index
integer(psb_ipk_), intent(out) :: info
real(psb_dpk_), intent(out) :: key
real(psb_dpk_), intent(inout) :: key
info = psb_success_

@ -67,8 +67,8 @@ module psb_e_hsort_mod
integer(psb_epk_), intent(in) :: key
integer(psb_epk_), intent(inout) :: heap(:)
integer(psb_ipk_), intent(in) :: dir
integer(psb_ipk_), intent(inout) :: last
integer(psb_epk_), intent(in) :: dir
integer(psb_epk_), intent(inout) :: last
integer(psb_ipk_), intent(out) :: info
end subroutine psi_e_insert_heap
end interface psi_insert_heap
@ -88,9 +88,9 @@ module psb_e_hsort_mod
integer(psb_epk_), intent(in) :: key
integer(psb_epk_), intent(inout) :: heap(:)
integer(psb_epk_), intent(in) :: index
integer(psb_ipk_), intent(in) :: dir
integer(psb_epk_), intent(in) :: dir
integer(psb_epk_), intent(inout) :: idxs(:)
integer(psb_ipk_), intent(inout) :: last
integer(psb_epk_), intent(inout) :: last
integer(psb_ipk_), intent(out) :: info
end subroutine psi_e_idx_insert_heap
end interface psi_idx_insert_heap
@ -101,8 +101,8 @@ module psb_e_hsort_mod
import
implicit none
integer(psb_epk_), intent(inout) :: key
integer(psb_ipk_), intent(inout) :: last
integer(psb_ipk_), intent(in) :: dir
integer(psb_epk_), intent(inout) :: last
integer(psb_epk_), intent(in) :: dir
integer(psb_epk_), intent(inout) :: heap(:)
integer(psb_ipk_), intent(out) :: info
end subroutine psi_e_heap_get_first
@ -114,8 +114,8 @@ module psb_e_hsort_mod
integer(psb_epk_), intent(inout) :: key
integer(psb_epk_), intent(out) :: index
integer(psb_epk_), intent(inout) :: heap(:)
integer(psb_ipk_), intent(in) :: dir
integer(psb_ipk_), intent(inout) :: last
integer(psb_epk_), intent(in) :: dir
integer(psb_epk_), intent(inout) :: last
integer(psb_epk_), intent(inout) :: idxs(:)
integer(psb_ipk_), intent(out) :: info
end subroutine psi_e_idx_heap_get_first

@ -46,7 +46,8 @@ module psb_i_hsort_x_mod
use psb_m_hsort_mod
type psb_i_heap
integer(psb_ipk_) :: last, dir
integer(psb_ipk_) :: dir
integer(psb_ipk_) :: last
integer(psb_ipk_), allocatable :: keys(:)
contains
procedure, pass(heap) :: init => psb_i_init_heap
@ -58,7 +59,8 @@ module psb_i_hsort_x_mod
end type psb_i_heap
type psb_i_idx_heap
integer(psb_ipk_) :: last, dir
integer(psb_ipk_) :: dir
integer(psb_ipk_) :: last
integer(psb_ipk_), allocatable :: keys(:)
integer(psb_ipk_), allocatable :: idxs(:)
contains
@ -122,7 +124,7 @@ contains
return
endif
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=psb_heap_resize)
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info /= psb_success_) then
write(psb_err_unit,*) 'Memory allocation failure in heap_insert'
info = -5
@ -235,9 +237,9 @@ contains
return
endif
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=psb_heap_resize)
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info == psb_success_) &
& call psb_ensure_size(heap%last+1,heap%idxs,info,addsz=psb_heap_resize)
& call psb_ensure_size(heap%last+1,heap%idxs,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info /= psb_success_) then
write(psb_err_unit,*) 'Memory allocation failure in heap_insert'
info = -5
@ -255,7 +257,7 @@ contains
class(psb_i_idx_heap), intent(inout) :: heap
integer(psb_ipk_), intent(out) :: index
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(out) :: key
integer(psb_ipk_), intent(inout) :: key
info = psb_success_

@ -46,7 +46,8 @@ module psb_l_hsort_x_mod
use psb_m_hsort_mod
type psb_l_heap
integer(psb_ipk_) :: last, dir
integer(psb_lpk_) :: dir
integer(psb_lpk_) :: last
integer(psb_lpk_), allocatable :: keys(:)
contains
procedure, pass(heap) :: init => psb_l_init_heap
@ -58,7 +59,8 @@ module psb_l_hsort_x_mod
end type psb_l_heap
type psb_l_idx_heap
integer(psb_ipk_) :: last, dir
integer(psb_lpk_) :: dir
integer(psb_lpk_) :: last
integer(psb_lpk_), allocatable :: keys(:)
integer(psb_lpk_), allocatable :: idxs(:)
contains
@ -122,7 +124,7 @@ contains
return
endif
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=psb_heap_resize)
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=(1_psb_lpk_)*psb_heap_resize)
if (info /= psb_success_) then
write(psb_err_unit,*) 'Memory allocation failure in heap_insert'
info = -5
@ -235,9 +237,9 @@ contains
return
endif
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=psb_heap_resize)
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=(1_psb_lpk_)*psb_heap_resize)
if (info == psb_success_) &
& call psb_ensure_size(heap%last+1,heap%idxs,info,addsz=psb_heap_resize)
& call psb_ensure_size(heap%last+1,heap%idxs,info,addsz=(1_psb_lpk_)*psb_heap_resize)
if (info /= psb_success_) then
write(psb_err_unit,*) 'Memory allocation failure in heap_insert'
info = -5
@ -255,7 +257,7 @@ contains
class(psb_l_idx_heap), intent(inout) :: heap
integer(psb_lpk_), intent(out) :: index
integer(psb_ipk_), intent(out) :: info
integer(psb_lpk_), intent(out) :: key
integer(psb_lpk_), intent(inout) :: key
info = psb_success_

@ -45,7 +45,8 @@ module psb_s_hsort_x_mod
use psb_s_hsort_mod
type psb_s_heap
integer(psb_ipk_) :: last, dir
integer(psb_ipk_) :: dir
integer(psb_ipk_) :: last
real(psb_spk_), allocatable :: keys(:)
contains
procedure, pass(heap) :: init => psb_s_init_heap
@ -57,7 +58,8 @@ module psb_s_hsort_x_mod
end type psb_s_heap
type psb_s_idx_heap
integer(psb_ipk_) :: last, dir
integer(psb_ipk_) :: dir
integer(psb_ipk_) :: last
real(psb_spk_), allocatable :: keys(:)
integer(psb_ipk_), allocatable :: idxs(:)
contains
@ -121,7 +123,7 @@ contains
return
endif
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=psb_heap_resize)
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info /= psb_success_) then
write(psb_err_unit,*) 'Memory allocation failure in heap_insert'
info = -5
@ -234,9 +236,9 @@ contains
return
endif
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=psb_heap_resize)
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info == psb_success_) &
& call psb_ensure_size(heap%last+1,heap%idxs,info,addsz=psb_heap_resize)
& call psb_ensure_size(heap%last+1,heap%idxs,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info /= psb_success_) then
write(psb_err_unit,*) 'Memory allocation failure in heap_insert'
info = -5
@ -254,7 +256,7 @@ contains
class(psb_s_idx_heap), intent(inout) :: heap
integer(psb_ipk_), intent(out) :: index
integer(psb_ipk_), intent(out) :: info
real(psb_spk_), intent(out) :: key
real(psb_spk_), intent(inout) :: key
info = psb_success_

@ -45,7 +45,8 @@ module psb_z_hsort_x_mod
use psb_z_hsort_mod
type psb_z_heap
integer(psb_ipk_) :: last, dir
integer(psb_ipk_) :: dir
integer(psb_ipk_) :: last
complex(psb_dpk_), allocatable :: keys(:)
contains
procedure, pass(heap) :: init => psb_z_init_heap
@ -57,7 +58,8 @@ module psb_z_hsort_x_mod
end type psb_z_heap
type psb_z_idx_heap
integer(psb_ipk_) :: last, dir
integer(psb_ipk_) :: dir
integer(psb_ipk_) :: last
complex(psb_dpk_), allocatable :: keys(:)
integer(psb_ipk_), allocatable :: idxs(:)
contains
@ -121,7 +123,7 @@ contains
return
endif
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=psb_heap_resize)
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info /= psb_success_) then
write(psb_err_unit,*) 'Memory allocation failure in heap_insert'
info = -5
@ -234,9 +236,9 @@ contains
return
endif
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=psb_heap_resize)
call psb_ensure_size(heap%last+1,heap%keys,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info == psb_success_) &
& call psb_ensure_size(heap%last+1,heap%idxs,info,addsz=psb_heap_resize)
& call psb_ensure_size(heap%last+1,heap%idxs,info,addsz=(1_psb_ipk_)*psb_heap_resize)
if (info /= psb_success_) then
write(psb_err_unit,*) 'Memory allocation failure in heap_insert'
info = -5
@ -254,7 +256,7 @@ contains
class(psb_z_idx_heap), intent(inout) :: heap
integer(psb_ipk_), intent(out) :: index
integer(psb_ipk_), intent(out) :: info
complex(psb_dpk_), intent(out) :: key
complex(psb_dpk_), intent(inout) :: key
info = psb_success_

@ -93,7 +93,7 @@ module psi_c_serial_mod
integer(psb_ipk_), intent(in) :: m
complex(psb_spk_), intent (in) :: x(:)
complex(psb_spk_), intent (in) :: y(:)
complex(psb_spk_), intent (in) :: z(:)
complex(psb_spk_), intent (inout) :: z(:)
complex(psb_spk_), intent (in) :: alpha, beta
integer(psb_ipk_), intent(out) :: info
end subroutine psi_caxpbyv2

@ -93,7 +93,7 @@ module psi_d_serial_mod
integer(psb_ipk_), intent(in) :: m
real(psb_dpk_), intent (in) :: x(:)
real(psb_dpk_), intent (in) :: y(:)
real(psb_dpk_), intent (in) :: z(:)
real(psb_dpk_), intent (inout) :: z(:)
real(psb_dpk_), intent (in) :: alpha, beta
integer(psb_ipk_), intent(out) :: info
end subroutine psi_daxpbyv2

@ -93,7 +93,7 @@ module psi_e_serial_mod
integer(psb_ipk_), intent(in) :: m
integer(psb_epk_), intent (in) :: x(:)
integer(psb_epk_), intent (in) :: y(:)
integer(psb_epk_), intent (in) :: z(:)
integer(psb_epk_), intent (inout) :: z(:)
integer(psb_epk_), intent (in) :: alpha, beta
integer(psb_ipk_), intent(out) :: info
end subroutine psi_eaxpbyv2

@ -93,7 +93,7 @@ module psi_i2_serial_mod
integer(psb_ipk_), intent(in) :: m
integer(psb_i2pk_), intent (in) :: x(:)
integer(psb_i2pk_), intent (in) :: y(:)
integer(psb_i2pk_), intent (in) :: z(:)
integer(psb_i2pk_), intent (inout) :: z(:)
integer(psb_i2pk_), intent (in) :: alpha, beta
integer(psb_ipk_), intent(out) :: info
end subroutine psi_i2axpbyv2

@ -93,7 +93,7 @@ module psi_m_serial_mod
integer(psb_ipk_), intent(in) :: m
integer(psb_mpk_), intent (in) :: x(:)
integer(psb_mpk_), intent (in) :: y(:)
integer(psb_mpk_), intent (in) :: z(:)
integer(psb_mpk_), intent (inout) :: z(:)
integer(psb_mpk_), intent (in) :: alpha, beta
integer(psb_ipk_), intent(out) :: info
end subroutine psi_maxpbyv2

@ -93,7 +93,7 @@ module psi_s_serial_mod
integer(psb_ipk_), intent(in) :: m
real(psb_spk_), intent (in) :: x(:)
real(psb_spk_), intent (in) :: y(:)
real(psb_spk_), intent (in) :: z(:)
real(psb_spk_), intent (inout) :: z(:)
real(psb_spk_), intent (in) :: alpha, beta
integer(psb_ipk_), intent(out) :: info
end subroutine psi_saxpbyv2

@ -93,7 +93,7 @@ module psi_z_serial_mod
integer(psb_ipk_), intent(in) :: m
complex(psb_dpk_), intent (in) :: x(:)
complex(psb_dpk_), intent (in) :: y(:)
complex(psb_dpk_), intent (in) :: z(:)
complex(psb_dpk_), intent (inout) :: z(:)
complex(psb_dpk_), intent (in) :: alpha, beta
integer(psb_ipk_), intent(out) :: info
end subroutine psi_zaxpbyv2

@ -296,7 +296,7 @@ module psb_indx_map_mod
implicit none
integer(psb_lpk_), intent(in) :: idx(:)
integer(psb_ipk_), allocatable, intent(out) :: iprc(:)
integer(psb_ipk_), allocatable, intent(inout) :: adj(:)
integer(psb_ipk_), intent(inout) :: adj(:)
class(psb_indx_map), intent(in) :: idxmap
integer(psb_ipk_), intent(out) :: info
end subroutine psi_adjcncy_fnd_owner

@ -87,10 +87,10 @@ module psi_i_mod
subroutine psi_i_csr_sort_dl(dl_ptr,c_dep_list,l_dep_list,ctxt,info)
import
implicit none
integer(psb_ipk_), intent(in) :: c_dep_list(:), dl_ptr(0:)
integer(psb_ipk_), intent(inout) :: l_dep_list(0:)
type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: info
integer(psb_ipk_), intent(in) :: dl_ptr(0:)
integer(psb_ipk_), intent(inout) :: c_dep_list(:), l_dep_list(0:)
type(psb_ctxt_type), intent(in) :: ctxt
integer(psb_ipk_), intent(out) :: info
end subroutine psi_i_csr_sort_dl
end interface

@ -642,7 +642,7 @@ subroutine psb_caxpbyvout(alpha, x, beta,y, z, desc_a,info)
end if
if(desc_a%get_local_rows() > 0) then
call caxpby(desc_a%get_local_cols(),ione,&
call caxpbyv2(desc_a%get_local_cols(),ione,&
& alpha,x,lldx,beta,&
& y,lldy,z,lldz,info)
end if

@ -642,7 +642,7 @@ subroutine psb_daxpbyvout(alpha, x, beta,y, z, desc_a,info)
end if
if(desc_a%get_local_rows() > 0) then
call daxpby(desc_a%get_local_cols(),ione,&
call daxpbyv2(desc_a%get_local_cols(),ione,&
& alpha,x,lldx,beta,&
& y,lldy,z,lldz,info)
end if

@ -642,7 +642,7 @@ subroutine psb_saxpbyvout(alpha, x, beta,y, z, desc_a,info)
end if
if(desc_a%get_local_rows() > 0) then
call saxpby(desc_a%get_local_cols(),ione,&
call saxpbyv2(desc_a%get_local_cols(),ione,&
& alpha,x,lldx,beta,&
& y,lldy,z,lldz,info)
end if

@ -642,7 +642,7 @@ subroutine psb_zaxpbyvout(alpha, x, beta,y, z, desc_a,info)
end if
if(desc_a%get_local_rows() > 0) then
call zaxpby(desc_a%get_local_cols(),ione,&
call zaxpbyv2(desc_a%get_local_cols(),ione,&
& alpha,x,lldx,beta,&
& y,lldy,z,lldz,info)
end if

@ -4616,7 +4616,7 @@ function psb_lc_coo_csnm1(a) result(res)
use psb_c_base_mat_mod, psb_protect_name => psb_lc_coo_csnm1
implicit none
class(psb_c_coo_sparse_mat), intent(in) :: a
class(psb_lc_coo_sparse_mat), intent(in) :: a
real(psb_spk_) :: res
integer(psb_lpk_) :: i,j,k,m,n, nnz, ir, jc, nc, info

@ -4616,7 +4616,7 @@ function psb_ld_coo_csnm1(a) result(res)
use psb_d_base_mat_mod, psb_protect_name => psb_ld_coo_csnm1
implicit none
class(psb_d_coo_sparse_mat), intent(in) :: a
class(psb_ld_coo_sparse_mat), intent(in) :: a
real(psb_dpk_) :: res
integer(psb_lpk_) :: i,j,k,m,n, nnz, ir, jc, nc, info

@ -4616,7 +4616,7 @@ function psb_ls_coo_csnm1(a) result(res)
use psb_s_base_mat_mod, psb_protect_name => psb_ls_coo_csnm1
implicit none
class(psb_s_coo_sparse_mat), intent(in) :: a
class(psb_ls_coo_sparse_mat), intent(in) :: a
real(psb_spk_) :: res
integer(psb_lpk_) :: i,j,k,m,n, nnz, ir, jc, nc, info

@ -4616,7 +4616,7 @@ function psb_lz_coo_csnm1(a) result(res)
use psb_z_base_mat_mod, psb_protect_name => psb_lz_coo_csnm1
implicit none
class(psb_z_coo_sparse_mat), intent(in) :: a
class(psb_lz_coo_sparse_mat), intent(in) :: a
real(psb_dpk_) :: res
integer(psb_lpk_) :: i,j,k,m,n, nnz, ir, jc, nc, info

@ -49,7 +49,8 @@ subroutine psb_chsort(x,ix,dir,flag)
integer(psb_ipk_), optional, intent(in) :: dir, flag
integer(psb_ipk_), optional, intent(inout) :: ix(:)
integer(psb_ipk_) :: dir_, flag_, n, i, l, err_act,info
integer(psb_ipk_) :: flag_, n, i, err_act,info
integer(psb_ipk_) :: dir_, l
complex(psb_spk_) :: key
integer(psb_ipk_) :: index
@ -159,7 +160,7 @@ end subroutine psb_chsort
!
! These are packaged so that they can be used to implement
! a heapsort, should the need arise
! a heapsort.
!
!
! Programming note:
@ -646,7 +647,8 @@ subroutine psi_c_idx_insert_heap(key,index,last,heap,idxs,dir,info)
! dir: sorting direction
complex(psb_spk_), intent(in) :: key
integer(psb_ipk_), intent(in) :: index,dir
integer(psb_ipk_), intent(in) :: index
integer(psb_ipk_), intent(in) :: dir
complex(psb_spk_), intent(inout) :: heap(:)
integer(psb_ipk_), intent(inout) :: idxs(:)
integer(psb_ipk_), intent(inout) :: last

@ -1,34 +1,34 @@
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! 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:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 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
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! 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.
!
!
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! 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:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 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
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! 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.
!
!
!
! The merge-sort routines
! References:
@ -41,7 +41,7 @@
! Addison-Wesley
!
subroutine psb_cmsort_u(x,nout,dir)
subroutine psb_cmsort_u(x,nout,dir)
use psb_sort_mod, psb_protect_name => psb_cmsort_u
use psb_error_mod
implicit none
@ -74,16 +74,10 @@
9999 call psb_error_handler(err_act)
return
end subroutine psb_cmsort_u
end subroutine psb_cmsort_u
subroutine psb_cmsort(x,ix,dir,flag)
subroutine psb_cmsort(x,ix,dir,flag)
use psb_sort_mod, psb_protect_name => psb_cmsort
use psb_error_mod
use psb_ip_reord_mod
@ -183,9 +177,9 @@
return
end subroutine psb_cmsort
end subroutine psb_cmsort
subroutine psi_c_lmsort_up(n,k,l,iret)
subroutine psi_c_lmsort_up(n,k,l,iret)
use psb_const_mod
use psi_lcx_mod
implicit none
@ -288,9 +282,9 @@
end do outer
end do mergepass
end subroutine psi_c_lmsort_up
end subroutine psi_c_lmsort_up
subroutine psi_c_lmsort_dw(n,k,l,iret)
subroutine psi_c_lmsort_dw(n,k,l,iret)
use psb_const_mod
use psi_lcx_mod
implicit none
@ -393,9 +387,9 @@
end do outer
end do mergepass
end subroutine psi_c_lmsort_dw
end subroutine psi_c_lmsort_dw
subroutine psi_c_amsort_up(n,k,l,iret)
subroutine psi_c_amsort_up(n,k,l,iret)
use psb_const_mod
use psi_acx_mod
implicit none
@ -498,9 +492,9 @@
end do outer
end do mergepass
end subroutine psi_c_amsort_up
end subroutine psi_c_amsort_up
subroutine psi_c_amsort_dw(n,k,l,iret)
subroutine psi_c_amsort_dw(n,k,l,iret)
use psb_const_mod
use psi_acx_mod
implicit none
@ -603,9 +597,9 @@
end do outer
end do mergepass
end subroutine psi_c_amsort_dw
end subroutine psi_c_amsort_dw
subroutine psi_c_almsort_up(n,k,l,iret)
subroutine psi_c_almsort_up(n,k,l,iret)
use psb_const_mod
use psi_alcx_mod
implicit none
@ -708,9 +702,9 @@
end do outer
end do mergepass
end subroutine psi_c_almsort_up
end subroutine psi_c_almsort_up
subroutine psi_c_almsort_dw(n,k,l,iret)
subroutine psi_c_almsort_dw(n,k,l,iret)
use psb_const_mod
use psi_alcx_mod
implicit none
@ -813,5 +807,5 @@
end do outer
end do mergepass
end subroutine psi_c_almsort_dw
end subroutine psi_c_almsort_dw

@ -49,7 +49,8 @@ subroutine psb_dhsort(x,ix,dir,flag)
integer(psb_ipk_), optional, intent(in) :: dir, flag
integer(psb_ipk_), optional, intent(inout) :: ix(:)
integer(psb_ipk_) :: dir_, flag_, n, i, l, err_act,info
integer(psb_ipk_) :: flag_, n, i, err_act,info
integer(psb_ipk_) :: dir_, l
real(psb_dpk_) :: key
integer(psb_ipk_) :: index
@ -159,7 +160,7 @@ end subroutine psb_dhsort
!
! These are packaged so that they can be used to implement
! a heapsort, should the need arise
! a heapsort.
!
!
! Programming note:
@ -540,11 +541,12 @@ subroutine psi_d_idx_heap_get_first(key,index,last,heap,idxs,dir,info)
use psb_sort_mod, psb_protect_name => psi_d_idx_heap_get_first
implicit none
real(psb_dpk_), intent(inout) :: key
real(psb_dpk_), intent(inout) :: heap(:)
integer(psb_ipk_), intent(out) :: index,info
integer(psb_ipk_), intent(out) :: index
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(inout) :: last,idxs(:)
integer(psb_ipk_), intent(in) :: dir
real(psb_dpk_), intent(out) :: key
integer(psb_ipk_) :: i, j,itemp
real(psb_dpk_) :: temp

@ -1,34 +1,34 @@
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! 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:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 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
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! 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.
!
!
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! 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:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 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
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! 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.
!
!
!
! The merge-sort routines
! References:
@ -41,7 +41,7 @@
! Addison-Wesley
!
subroutine psb_dmsort_u(x,nout,dir)
subroutine psb_dmsort_u(x,nout,dir)
use psb_sort_mod, psb_protect_name => psb_dmsort_u
use psb_error_mod
implicit none
@ -74,10 +74,10 @@
9999 call psb_error_handler(err_act)
return
end subroutine psb_dmsort_u
end subroutine psb_dmsort_u
function psb_dbsrch(key,n,v) result(ipos)
function psb_dbsrch(key,n,v) result(ipos)
use psb_sort_mod, psb_protect_name => psb_dbsrch
implicit none
integer(psb_ipk_) :: ipos, n
@ -112,9 +112,9 @@
end if
enddo
return
end function psb_dbsrch
end function psb_dbsrch
function psb_dssrch(key,n,v) result(ipos)
function psb_dssrch(key,n,v) result(ipos)
use psb_sort_mod, psb_protect_name => psb_dssrch
implicit none
integer(psb_ipk_) :: ipos, n
@ -132,9 +132,9 @@
enddo
return
end function psb_dssrch
end function psb_dssrch
subroutine psb_dmsort(x,ix,dir,flag)
subroutine psb_dmsort(x,ix,dir,flag)
use psb_sort_mod, psb_protect_name => psb_dmsort
use psb_error_mod
use psb_ip_reord_mod
@ -231,9 +231,9 @@
return
end subroutine psb_dmsort
end subroutine psb_dmsort
subroutine psi_d_msort_up(n,k,l,iret)
subroutine psi_d_msort_up(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -335,9 +335,9 @@
end do outer
end do mergepass
end subroutine psi_d_msort_up
end subroutine psi_d_msort_up
subroutine psi_d_msort_dw(n,k,l,iret)
subroutine psi_d_msort_dw(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -439,9 +439,9 @@
end do outer
end do mergepass
end subroutine psi_d_msort_dw
end subroutine psi_d_msort_dw
subroutine psi_d_amsort_up(n,k,l,iret)
subroutine psi_d_amsort_up(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -543,9 +543,9 @@
end do outer
end do mergepass
end subroutine psi_d_amsort_up
end subroutine psi_d_amsort_up
subroutine psi_d_amsort_dw(n,k,l,iret)
subroutine psi_d_amsort_dw(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -647,12 +647,6 @@
end do outer
end do mergepass
end subroutine psi_d_amsort_dw
end subroutine psi_d_amsort_dw

@ -49,7 +49,8 @@ subroutine psb_ehsort(x,ix,dir,flag)
integer(psb_ipk_), optional, intent(in) :: dir, flag
integer(psb_epk_), optional, intent(inout) :: ix(:)
integer(psb_ipk_) :: dir_, flag_, n, i, l, err_act,info
integer(psb_ipk_) :: flag_, n, i, err_act,info
integer(psb_epk_) :: dir_, l
integer(psb_epk_) :: key
integer(psb_epk_) :: index
@ -159,7 +160,7 @@ end subroutine psb_ehsort
!
! These are packaged so that they can be used to implement
! a heapsort, should the need arise
! a heapsort.
!
!
! Programming note:
@ -196,7 +197,7 @@ subroutine psi_e_insert_heap(key,last,heap,dir,info)
! dir: sorting direction
integer(psb_epk_), intent(in) :: key
integer(psb_ipk_), intent(in) :: dir
integer(psb_epk_), intent(in) :: dir
integer(psb_epk_), intent(inout) :: heap(:)
integer(psb_epk_), intent(inout) :: last
integer(psb_ipk_), intent(out) :: info
@ -296,7 +297,7 @@ subroutine psi_e_heap_get_first(key,last,heap,dir,info)
integer(psb_epk_), intent(inout) :: key
integer(psb_epk_), intent(inout) :: last
integer(psb_ipk_), intent(in) :: dir
integer(psb_epk_), intent(in) :: dir
integer(psb_epk_), intent(inout) :: heap(:)
integer(psb_ipk_), intent(out) :: info
@ -428,9 +429,9 @@ subroutine psi_e_idx_insert_heap(key,index,last,heap,idxs,dir,info)
! dir: sorting direction
integer(psb_epk_), intent(in) :: key
integer(psb_ipk_), intent(in) :: index,dir
integer(psb_epk_), intent(in) :: index,dir
integer(psb_epk_), intent(inout) :: heap(:)
integer(psb_ipk_), intent(inout) :: idxs(:),last
integer(psb_epk_), intent(inout) :: idxs(:),last
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: i, i2, itemp
integer(psb_epk_) :: temp
@ -540,11 +541,12 @@ subroutine psi_e_idx_heap_get_first(key,index,last,heap,idxs,dir,info)
use psb_sort_mod, psb_protect_name => psi_e_idx_heap_get_first
implicit none
integer(psb_epk_), intent(inout) :: key
integer(psb_epk_), intent(inout) :: heap(:)
integer(psb_ipk_), intent(out) :: index,info
integer(psb_ipk_), intent(inout) :: last,idxs(:)
integer(psb_ipk_), intent(in) :: dir
integer(psb_epk_), intent(out) :: key
integer(psb_epk_), intent(out) :: index
integer(psb_ipk_), intent(out) :: info
integer(psb_epk_), intent(inout) :: last,idxs(:)
integer(psb_epk_), intent(in) :: dir
integer(psb_ipk_) :: i, j,itemp
integer(psb_epk_) :: temp

@ -1,34 +1,34 @@
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! 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:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 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
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! 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.
!
!
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! 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:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 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
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! 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.
!
!
!
! The merge-sort routines
! References:
@ -40,7 +40,7 @@
! Data Structures and Algorithms
! Addison-Wesley
!
logical function psb_eisaperm(n,eip)
logical function psb_eisaperm(n,eip)
use psb_sort_mod, psb_protect_name => psb_eisaperm
implicit none
@ -93,10 +93,10 @@
9999 continue
return
end function psb_eisaperm
end function psb_eisaperm
subroutine psb_emsort_u(x,nout,dir)
subroutine psb_emsort_u(x,nout,dir)
use psb_sort_mod, psb_protect_name => psb_emsort_u
use psb_error_mod
implicit none
@ -129,10 +129,10 @@
9999 call psb_error_handler(err_act)
return
end subroutine psb_emsort_u
end subroutine psb_emsort_u
function psb_ebsrch(key,n,v) result(ipos)
function psb_ebsrch(key,n,v) result(ipos)
use psb_sort_mod, psb_protect_name => psb_ebsrch
implicit none
integer(psb_ipk_) :: ipos, n
@ -167,9 +167,9 @@
end if
enddo
return
end function psb_ebsrch
end function psb_ebsrch
function psb_essrch(key,n,v) result(ipos)
function psb_essrch(key,n,v) result(ipos)
use psb_sort_mod, psb_protect_name => psb_essrch
implicit none
integer(psb_ipk_) :: ipos, n
@ -187,9 +187,9 @@
enddo
return
end function psb_essrch
end function psb_essrch
subroutine psb_emsort(x,ix,dir,flag)
subroutine psb_emsort(x,ix,dir,flag)
use psb_sort_mod, psb_protect_name => psb_emsort
use psb_error_mod
use psb_ip_reord_mod
@ -286,9 +286,9 @@
return
end subroutine psb_emsort
end subroutine psb_emsort
subroutine psi_e_msort_up(n,k,l,iret)
subroutine psi_e_msort_up(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -390,9 +390,9 @@
end do outer
end do mergepass
end subroutine psi_e_msort_up
end subroutine psi_e_msort_up
subroutine psi_e_msort_dw(n,k,l,iret)
subroutine psi_e_msort_dw(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -494,9 +494,9 @@
end do outer
end do mergepass
end subroutine psi_e_msort_dw
end subroutine psi_e_msort_dw
subroutine psi_e_amsort_up(n,k,l,iret)
subroutine psi_e_amsort_up(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -598,9 +598,9 @@
end do outer
end do mergepass
end subroutine psi_e_amsort_up
end subroutine psi_e_amsort_up
subroutine psi_e_amsort_dw(n,k,l,iret)
subroutine psi_e_amsort_dw(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -702,12 +702,6 @@
end do outer
end do mergepass
end subroutine psi_e_amsort_dw
end subroutine psi_e_amsort_dw

@ -49,7 +49,8 @@ subroutine psb_mhsort(x,ix,dir,flag)
integer(psb_ipk_), optional, intent(in) :: dir, flag
integer(psb_ipk_), optional, intent(inout) :: ix(:)
integer(psb_ipk_) :: dir_, flag_, n, i, l, err_act,info
integer(psb_ipk_) :: flag_, n, i, err_act,info
integer(psb_ipk_) :: dir_, l
integer(psb_mpk_) :: key
integer(psb_ipk_) :: index
@ -159,7 +160,7 @@ end subroutine psb_mhsort
!
! These are packaged so that they can be used to implement
! a heapsort, should the need arise
! a heapsort.
!
!
! Programming note:
@ -540,11 +541,12 @@ subroutine psi_m_idx_heap_get_first(key,index,last,heap,idxs,dir,info)
use psb_sort_mod, psb_protect_name => psi_m_idx_heap_get_first
implicit none
integer(psb_mpk_), intent(inout) :: key
integer(psb_mpk_), intent(inout) :: heap(:)
integer(psb_ipk_), intent(out) :: index,info
integer(psb_ipk_), intent(out) :: index
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(inout) :: last,idxs(:)
integer(psb_ipk_), intent(in) :: dir
integer(psb_mpk_), intent(out) :: key
integer(psb_ipk_) :: i, j,itemp
integer(psb_mpk_) :: temp

@ -1,34 +1,34 @@
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! 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:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 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
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! 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.
!
!
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! 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:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 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
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! 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.
!
!
!
! The merge-sort routines
! References:
@ -40,7 +40,7 @@
! Data Structures and Algorithms
! Addison-Wesley
!
logical function psb_misaperm(n,eip)
logical function psb_misaperm(n,eip)
use psb_sort_mod, psb_protect_name => psb_misaperm
implicit none
@ -93,10 +93,10 @@
9999 continue
return
end function psb_misaperm
end function psb_misaperm
subroutine psb_mmsort_u(x,nout,dir)
subroutine psb_mmsort_u(x,nout,dir)
use psb_sort_mod, psb_protect_name => psb_mmsort_u
use psb_error_mod
implicit none
@ -129,10 +129,10 @@
9999 call psb_error_handler(err_act)
return
end subroutine psb_mmsort_u
end subroutine psb_mmsort_u
function psb_mbsrch(key,n,v) result(ipos)
function psb_mbsrch(key,n,v) result(ipos)
use psb_sort_mod, psb_protect_name => psb_mbsrch
implicit none
integer(psb_ipk_) :: ipos, n
@ -167,9 +167,9 @@
end if
enddo
return
end function psb_mbsrch
end function psb_mbsrch
function psb_mssrch(key,n,v) result(ipos)
function psb_mssrch(key,n,v) result(ipos)
use psb_sort_mod, psb_protect_name => psb_mssrch
implicit none
integer(psb_ipk_) :: ipos, n
@ -187,9 +187,9 @@
enddo
return
end function psb_mssrch
end function psb_mssrch
subroutine psb_mmsort(x,ix,dir,flag)
subroutine psb_mmsort(x,ix,dir,flag)
use psb_sort_mod, psb_protect_name => psb_mmsort
use psb_error_mod
use psb_ip_reord_mod
@ -286,9 +286,9 @@
return
end subroutine psb_mmsort
end subroutine psb_mmsort
subroutine psi_m_msort_up(n,k,l,iret)
subroutine psi_m_msort_up(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -390,9 +390,9 @@
end do outer
end do mergepass
end subroutine psi_m_msort_up
end subroutine psi_m_msort_up
subroutine psi_m_msort_dw(n,k,l,iret)
subroutine psi_m_msort_dw(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -494,9 +494,9 @@
end do outer
end do mergepass
end subroutine psi_m_msort_dw
end subroutine psi_m_msort_dw
subroutine psi_m_amsort_up(n,k,l,iret)
subroutine psi_m_amsort_up(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -598,9 +598,9 @@
end do outer
end do mergepass
end subroutine psi_m_amsort_up
end subroutine psi_m_amsort_up
subroutine psi_m_amsort_dw(n,k,l,iret)
subroutine psi_m_amsort_dw(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -702,12 +702,6 @@
end do outer
end do mergepass
end subroutine psi_m_amsort_dw
end subroutine psi_m_amsort_dw

@ -49,7 +49,8 @@ subroutine psb_shsort(x,ix,dir,flag)
integer(psb_ipk_), optional, intent(in) :: dir, flag
integer(psb_ipk_), optional, intent(inout) :: ix(:)
integer(psb_ipk_) :: dir_, flag_, n, i, l, err_act,info
integer(psb_ipk_) :: flag_, n, i, err_act,info
integer(psb_ipk_) :: dir_, l
real(psb_spk_) :: key
integer(psb_ipk_) :: index
@ -159,7 +160,7 @@ end subroutine psb_shsort
!
! These are packaged so that they can be used to implement
! a heapsort, should the need arise
! a heapsort.
!
!
! Programming note:
@ -540,11 +541,12 @@ subroutine psi_s_idx_heap_get_first(key,index,last,heap,idxs,dir,info)
use psb_sort_mod, psb_protect_name => psi_s_idx_heap_get_first
implicit none
real(psb_spk_), intent(inout) :: key
real(psb_spk_), intent(inout) :: heap(:)
integer(psb_ipk_), intent(out) :: index,info
integer(psb_ipk_), intent(out) :: index
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(inout) :: last,idxs(:)
integer(psb_ipk_), intent(in) :: dir
real(psb_spk_), intent(out) :: key
integer(psb_ipk_) :: i, j,itemp
real(psb_spk_) :: temp

@ -1,34 +1,34 @@
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! 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:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 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
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! 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.
!
!
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! 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:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 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
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! 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.
!
!
!
! The merge-sort routines
! References:
@ -41,7 +41,7 @@
! Addison-Wesley
!
subroutine psb_smsort_u(x,nout,dir)
subroutine psb_smsort_u(x,nout,dir)
use psb_sort_mod, psb_protect_name => psb_smsort_u
use psb_error_mod
implicit none
@ -74,10 +74,10 @@
9999 call psb_error_handler(err_act)
return
end subroutine psb_smsort_u
end subroutine psb_smsort_u
function psb_sbsrch(key,n,v) result(ipos)
function psb_sbsrch(key,n,v) result(ipos)
use psb_sort_mod, psb_protect_name => psb_sbsrch
implicit none
integer(psb_ipk_) :: ipos, n
@ -112,9 +112,9 @@
end if
enddo
return
end function psb_sbsrch
end function psb_sbsrch
function psb_sssrch(key,n,v) result(ipos)
function psb_sssrch(key,n,v) result(ipos)
use psb_sort_mod, psb_protect_name => psb_sssrch
implicit none
integer(psb_ipk_) :: ipos, n
@ -132,9 +132,9 @@
enddo
return
end function psb_sssrch
end function psb_sssrch
subroutine psb_smsort(x,ix,dir,flag)
subroutine psb_smsort(x,ix,dir,flag)
use psb_sort_mod, psb_protect_name => psb_smsort
use psb_error_mod
use psb_ip_reord_mod
@ -231,9 +231,9 @@
return
end subroutine psb_smsort
end subroutine psb_smsort
subroutine psi_s_msort_up(n,k,l,iret)
subroutine psi_s_msort_up(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -335,9 +335,9 @@
end do outer
end do mergepass
end subroutine psi_s_msort_up
end subroutine psi_s_msort_up
subroutine psi_s_msort_dw(n,k,l,iret)
subroutine psi_s_msort_dw(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -439,9 +439,9 @@
end do outer
end do mergepass
end subroutine psi_s_msort_dw
end subroutine psi_s_msort_dw
subroutine psi_s_amsort_up(n,k,l,iret)
subroutine psi_s_amsort_up(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -543,9 +543,9 @@
end do outer
end do mergepass
end subroutine psi_s_amsort_up
end subroutine psi_s_amsort_up
subroutine psi_s_amsort_dw(n,k,l,iret)
subroutine psi_s_amsort_dw(n,k,l,iret)
use psb_const_mod
implicit none
integer(psb_ipk_) :: n, iret
@ -647,12 +647,6 @@
end do outer
end do mergepass
end subroutine psi_s_amsort_dw
end subroutine psi_s_amsort_dw

@ -49,7 +49,8 @@ subroutine psb_zhsort(x,ix,dir,flag)
integer(psb_ipk_), optional, intent(in) :: dir, flag
integer(psb_ipk_), optional, intent(inout) :: ix(:)
integer(psb_ipk_) :: dir_, flag_, n, i, l, err_act,info
integer(psb_ipk_) :: flag_, n, i, err_act,info
integer(psb_ipk_) :: dir_, l
complex(psb_dpk_) :: key
integer(psb_ipk_) :: index
@ -159,7 +160,7 @@ end subroutine psb_zhsort
!
! These are packaged so that they can be used to implement
! a heapsort, should the need arise
! a heapsort.
!
!
! Programming note:
@ -646,7 +647,8 @@ subroutine psi_z_idx_insert_heap(key,index,last,heap,idxs,dir,info)
! dir: sorting direction
complex(psb_dpk_), intent(in) :: key
integer(psb_ipk_), intent(in) :: index,dir
integer(psb_ipk_), intent(in) :: index
integer(psb_ipk_), intent(in) :: dir
complex(psb_dpk_), intent(inout) :: heap(:)
integer(psb_ipk_), intent(inout) :: idxs(:)
integer(psb_ipk_), intent(inout) :: last

@ -1,34 +1,34 @@
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! 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:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 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
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! 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.
!
!
!
! Parallel Sparse BLAS version 3.5
! (C) Copyright 2006-2018
! 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:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 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
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! 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.
!
!
!
! The merge-sort routines
! References:
@ -41,7 +41,7 @@
! Addison-Wesley
!
subroutine psb_zmsort_u(x,nout,dir)
subroutine psb_zmsort_u(x,nout,dir)
use psb_sort_mod, psb_protect_name => psb_zmsort_u
use psb_error_mod
implicit none
@ -74,16 +74,10 @@
9999 call psb_error_handler(err_act)
return
end subroutine psb_zmsort_u
end subroutine psb_zmsort_u
subroutine psb_zmsort(x,ix,dir,flag)
subroutine psb_zmsort(x,ix,dir,flag)
use psb_sort_mod, psb_protect_name => psb_zmsort
use psb_error_mod
use psb_ip_reord_mod
@ -183,9 +177,9 @@
return
end subroutine psb_zmsort
end subroutine psb_zmsort
subroutine psi_z_lmsort_up(n,k,l,iret)
subroutine psi_z_lmsort_up(n,k,l,iret)
use psb_const_mod
use psi_lcx_mod
implicit none
@ -288,9 +282,9 @@
end do outer
end do mergepass
end subroutine psi_z_lmsort_up
end subroutine psi_z_lmsort_up
subroutine psi_z_lmsort_dw(n,k,l,iret)
subroutine psi_z_lmsort_dw(n,k,l,iret)
use psb_const_mod
use psi_lcx_mod
implicit none
@ -393,9 +387,9 @@
end do outer
end do mergepass
end subroutine psi_z_lmsort_dw
end subroutine psi_z_lmsort_dw
subroutine psi_z_amsort_up(n,k,l,iret)
subroutine psi_z_amsort_up(n,k,l,iret)
use psb_const_mod
use psi_acx_mod
implicit none
@ -498,9 +492,9 @@
end do outer
end do mergepass
end subroutine psi_z_amsort_up
end subroutine psi_z_amsort_up
subroutine psi_z_amsort_dw(n,k,l,iret)
subroutine psi_z_amsort_dw(n,k,l,iret)
use psb_const_mod
use psi_acx_mod
implicit none
@ -603,9 +597,9 @@
end do outer
end do mergepass
end subroutine psi_z_amsort_dw
end subroutine psi_z_amsort_dw
subroutine psi_z_almsort_up(n,k,l,iret)
subroutine psi_z_almsort_up(n,k,l,iret)
use psb_const_mod
use psi_alcx_mod
implicit none
@ -708,9 +702,9 @@
end do outer
end do mergepass
end subroutine psi_z_almsort_up
end subroutine psi_z_almsort_up
subroutine psi_z_almsort_dw(n,k,l,iret)
subroutine psi_z_almsort_dw(n,k,l,iret)
use psb_const_mod
use psi_alcx_mod
implicit none
@ -813,5 +807,5 @@
end do outer
end do mergepass
end subroutine psi_z_almsort_dw
end subroutine psi_z_almsort_dw

Loading…
Cancel
Save