First round of cleanup build warnings

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

@ -64,7 +64,7 @@ subroutine psb_dgather_vect(globx, locx, desc_a, info, iroot)
real(psb_dpk_), allocatable :: llocx(:) real(psb_dpk_), allocatable :: llocx(:)
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
name='psb_cgatherv' name='psb_dgatherv'
info=psb_success_ info=psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
if (psb_errstatus_fatal()) then if (psb_errstatus_fatal()) then
@ -182,7 +182,7 @@ subroutine psb_dgather_multivect(globx, locx, desc_a, info, iroot)
real(psb_dpk_), allocatable :: llocx(:,:) real(psb_dpk_), allocatable :: llocx(:,:)
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
name='psb_cgatherv' name='psb_dgatherv'
info=psb_success_ info=psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
if (psb_errstatus_fatal()) then if (psb_errstatus_fatal()) then

@ -64,7 +64,7 @@ subroutine psb_igather_vect(globx, locx, desc_a, info, iroot)
integer(psb_ipk_), allocatable :: llocx(:) integer(psb_ipk_), allocatable :: llocx(:)
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
name='psb_cgatherv' name='psb_igatherv'
info=psb_success_ info=psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
if (psb_errstatus_fatal()) then if (psb_errstatus_fatal()) then
@ -182,7 +182,7 @@ subroutine psb_igather_multivect(globx, locx, desc_a, info, iroot)
integer(psb_ipk_), allocatable :: llocx(:,:) integer(psb_ipk_), allocatable :: llocx(:,:)
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
name='psb_cgatherv' name='psb_igatherv'
info=psb_success_ info=psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
if (psb_errstatus_fatal()) then if (psb_errstatus_fatal()) then

@ -64,7 +64,7 @@ subroutine psb_lgather_vect(globx, locx, desc_a, info, iroot)
integer(psb_lpk_), allocatable :: llocx(:) integer(psb_lpk_), allocatable :: llocx(:)
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
name='psb_cgatherv' name='psb_lgatherv'
info=psb_success_ info=psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
if (psb_errstatus_fatal()) then if (psb_errstatus_fatal()) then
@ -182,7 +182,7 @@ subroutine psb_lgather_multivect(globx, locx, desc_a, info, iroot)
integer(psb_lpk_), allocatable :: llocx(:,:) integer(psb_lpk_), allocatable :: llocx(:,:)
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
name='psb_cgatherv' name='psb_lgatherv'
info=psb_success_ info=psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
if (psb_errstatus_fatal()) then if (psb_errstatus_fatal()) then

@ -64,7 +64,7 @@ subroutine psb_sgather_vect(globx, locx, desc_a, info, iroot)
real(psb_spk_), allocatable :: llocx(:) real(psb_spk_), allocatable :: llocx(:)
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
name='psb_cgatherv' name='psb_sgatherv'
info=psb_success_ info=psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
if (psb_errstatus_fatal()) then if (psb_errstatus_fatal()) then
@ -182,7 +182,7 @@ subroutine psb_sgather_multivect(globx, locx, desc_a, info, iroot)
real(psb_spk_), allocatable :: llocx(:,:) real(psb_spk_), allocatable :: llocx(:,:)
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
name='psb_cgatherv' name='psb_sgatherv'
info=psb_success_ info=psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
if (psb_errstatus_fatal()) then if (psb_errstatus_fatal()) then

@ -64,7 +64,7 @@ subroutine psb_zgather_vect(globx, locx, desc_a, info, iroot)
complex(psb_dpk_), allocatable :: llocx(:) complex(psb_dpk_), allocatable :: llocx(:)
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
name='psb_cgatherv' name='psb_zgatherv'
info=psb_success_ info=psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
if (psb_errstatus_fatal()) then if (psb_errstatus_fatal()) then
@ -182,7 +182,7 @@ subroutine psb_zgather_multivect(globx, locx, desc_a, info, iroot)
complex(psb_dpk_), allocatable :: llocx(:,:) complex(psb_dpk_), allocatable :: llocx(:,:)
character(len=20) :: name, ch_err character(len=20) :: name, ch_err
name='psb_cgatherv' name='psb_zgatherv'
info=psb_success_ info=psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
if (psb_errstatus_fatal()) then if (psb_errstatus_fatal()) then

@ -138,7 +138,7 @@ module psb_c_comm_mod
import import
implicit none implicit none
type(psb_c_multivect_type), intent(inout) :: locx type(psb_c_multivect_type), intent(inout) :: locx
complex(psb_spk_), intent(out), allocatable :: globx(:) complex(psb_spk_), intent(out), allocatable :: globx(:,:)
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root

@ -138,7 +138,7 @@ module psb_d_comm_mod
import import
implicit none implicit none
type(psb_d_multivect_type), intent(inout) :: locx type(psb_d_multivect_type), intent(inout) :: locx
real(psb_dpk_), intent(out), allocatable :: globx(:) real(psb_dpk_), intent(out), allocatable :: globx(:,:)
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root

@ -107,7 +107,7 @@ module psb_i_comm_mod
import import
implicit none implicit none
type(psb_i_multivect_type), intent(inout) :: locx type(psb_i_multivect_type), intent(inout) :: locx
integer(psb_ipk_), intent(out), allocatable :: globx(:) integer(psb_ipk_), intent(out), allocatable :: globx(:,:)
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root

@ -107,7 +107,7 @@ module psb_l_comm_mod
import import
implicit none implicit none
type(psb_l_multivect_type), intent(inout) :: locx type(psb_l_multivect_type), intent(inout) :: locx
integer(psb_lpk_), intent(out), allocatable :: globx(:) integer(psb_lpk_), intent(out), allocatable :: globx(:,:)
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root

@ -138,7 +138,7 @@ module psb_s_comm_mod
import import
implicit none implicit none
type(psb_s_multivect_type), intent(inout) :: locx type(psb_s_multivect_type), intent(inout) :: locx
real(psb_spk_), intent(out), allocatable :: globx(:) real(psb_spk_), intent(out), allocatable :: globx(:,:)
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root

@ -138,7 +138,7 @@ module psb_z_comm_mod
import import
implicit none implicit none
type(psb_z_multivect_type), intent(inout) :: locx type(psb_z_multivect_type), intent(inout) :: locx
complex(psb_dpk_), intent(out), allocatable :: globx(:) complex(psb_dpk_), intent(out), allocatable :: globx(:,:)
type(psb_desc_type), intent(in) :: desc_a type(psb_desc_type), intent(in) :: desc_a
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root

@ -947,8 +947,8 @@ module psb_c_mat_mod
interface interface
subroutine psb_c_cp_from_lb(a,b) subroutine psb_c_cp_from_lb(a,b)
import :: psb_ipk_, psb_lpk_, psb_cspmat_type, psb_spk_, psb_lc_base_sparse_mat import :: psb_ipk_, psb_lpk_, psb_cspmat_type, psb_spk_, psb_lc_base_sparse_mat
class(psb_cspmat_type), intent(out) :: a class(psb_cspmat_type), intent(inout) :: a
class(psb_lc_base_sparse_mat), intent(in) :: b class(psb_lc_base_sparse_mat), intent(inout) :: b
end subroutine psb_c_cp_from_lb end subroutine psb_c_cp_from_lb
end interface end interface
@ -1731,8 +1731,8 @@ module psb_c_mat_mod
interface interface
subroutine psb_lc_cp_from_ib(a,b) subroutine psb_lc_cp_from_ib(a,b)
import :: psb_ipk_, psb_lpk_, psb_lcspmat_type, psb_spk_, psb_c_base_sparse_mat import :: psb_ipk_, psb_lpk_, psb_lcspmat_type, psb_spk_, psb_c_base_sparse_mat
class(psb_lcspmat_type), intent(out) :: a class(psb_lcspmat_type), intent(inout) :: a
class(psb_c_base_sparse_mat), intent(in) :: b class(psb_c_base_sparse_mat), intent(inout) :: b
end subroutine psb_lc_cp_from_ib end subroutine psb_lc_cp_from_ib
end interface end interface

@ -947,8 +947,8 @@ module psb_d_mat_mod
interface interface
subroutine psb_d_cp_from_lb(a,b) subroutine psb_d_cp_from_lb(a,b)
import :: psb_ipk_, psb_lpk_, psb_dspmat_type, psb_dpk_, psb_ld_base_sparse_mat import :: psb_ipk_, psb_lpk_, psb_dspmat_type, psb_dpk_, psb_ld_base_sparse_mat
class(psb_dspmat_type), intent(out) :: a class(psb_dspmat_type), intent(inout) :: a
class(psb_ld_base_sparse_mat), intent(in) :: b class(psb_ld_base_sparse_mat), intent(inout) :: b
end subroutine psb_d_cp_from_lb end subroutine psb_d_cp_from_lb
end interface end interface
@ -1731,8 +1731,8 @@ module psb_d_mat_mod
interface interface
subroutine psb_ld_cp_from_ib(a,b) subroutine psb_ld_cp_from_ib(a,b)
import :: psb_ipk_, psb_lpk_, psb_ldspmat_type, psb_dpk_, psb_d_base_sparse_mat import :: psb_ipk_, psb_lpk_, psb_ldspmat_type, psb_dpk_, psb_d_base_sparse_mat
class(psb_ldspmat_type), intent(out) :: a class(psb_ldspmat_type), intent(inout) :: a
class(psb_d_base_sparse_mat), intent(in) :: b class(psb_d_base_sparse_mat), intent(inout) :: b
end subroutine psb_ld_cp_from_ib end subroutine psb_ld_cp_from_ib
end interface end interface

@ -947,8 +947,8 @@ module psb_s_mat_mod
interface interface
subroutine psb_s_cp_from_lb(a,b) subroutine psb_s_cp_from_lb(a,b)
import :: psb_ipk_, psb_lpk_, psb_sspmat_type, psb_spk_, psb_ls_base_sparse_mat import :: psb_ipk_, psb_lpk_, psb_sspmat_type, psb_spk_, psb_ls_base_sparse_mat
class(psb_sspmat_type), intent(out) :: a class(psb_sspmat_type), intent(inout) :: a
class(psb_ls_base_sparse_mat), intent(in) :: b class(psb_ls_base_sparse_mat), intent(inout) :: b
end subroutine psb_s_cp_from_lb end subroutine psb_s_cp_from_lb
end interface end interface
@ -1731,8 +1731,8 @@ module psb_s_mat_mod
interface interface
subroutine psb_ls_cp_from_ib(a,b) subroutine psb_ls_cp_from_ib(a,b)
import :: psb_ipk_, psb_lpk_, psb_lsspmat_type, psb_spk_, psb_s_base_sparse_mat import :: psb_ipk_, psb_lpk_, psb_lsspmat_type, psb_spk_, psb_s_base_sparse_mat
class(psb_lsspmat_type), intent(out) :: a class(psb_lsspmat_type), intent(inout) :: a
class(psb_s_base_sparse_mat), intent(in) :: b class(psb_s_base_sparse_mat), intent(inout) :: b
end subroutine psb_ls_cp_from_ib end subroutine psb_ls_cp_from_ib
end interface end interface

@ -947,8 +947,8 @@ module psb_z_mat_mod
interface interface
subroutine psb_z_cp_from_lb(a,b) subroutine psb_z_cp_from_lb(a,b)
import :: psb_ipk_, psb_lpk_, psb_zspmat_type, psb_dpk_, psb_lz_base_sparse_mat import :: psb_ipk_, psb_lpk_, psb_zspmat_type, psb_dpk_, psb_lz_base_sparse_mat
class(psb_zspmat_type), intent(out) :: a class(psb_zspmat_type), intent(inout) :: a
class(psb_lz_base_sparse_mat), intent(in) :: b class(psb_lz_base_sparse_mat), intent(inout) :: b
end subroutine psb_z_cp_from_lb end subroutine psb_z_cp_from_lb
end interface end interface
@ -1731,8 +1731,8 @@ module psb_z_mat_mod
interface interface
subroutine psb_lz_cp_from_ib(a,b) subroutine psb_lz_cp_from_ib(a,b)
import :: psb_ipk_, psb_lpk_, psb_lzspmat_type, psb_dpk_, psb_z_base_sparse_mat import :: psb_ipk_, psb_lpk_, psb_lzspmat_type, psb_dpk_, psb_z_base_sparse_mat
class(psb_lzspmat_type), intent(out) :: a class(psb_lzspmat_type), intent(inout) :: a
class(psb_z_base_sparse_mat), intent(in) :: b class(psb_z_base_sparse_mat), intent(inout) :: b
end subroutine psb_lz_cp_from_ib end subroutine psb_lz_cp_from_ib
end interface end interface

@ -91,9 +91,9 @@ subroutine psb_base_sparse_print(iout,a,iv,head,ivr,ivc)
integer(psb_ipk_), intent(in) :: iout integer(psb_ipk_), intent(in) :: iout
class(psb_base_sparse_mat), intent(in) :: a class(psb_base_sparse_mat), intent(in) :: a
integer(psb_ipk_), intent(in), optional :: iv(:) integer(psb_lpk_), intent(in), optional :: iv(:)
character(len=*), optional :: head character(len=*), optional :: head
integer(psb_ipk_), intent(in), optional :: ivr(:), ivc(:) integer(psb_lpk_), intent(in), optional :: ivr(:), ivc(:)
integer(psb_ipk_) :: err_act, info integer(psb_ipk_) :: err_act, info
character(len=20) :: name='sparse_print' character(len=20) :: name='sparse_print'
@ -384,7 +384,7 @@ subroutine psb_lbase_sparse_print(iout,a,iv,head,ivr,ivc)
use psb_error_mod use psb_error_mod
implicit none implicit none
integer(psb_lpk_), intent(in) :: iout integer(psb_ipk_), intent(in) :: iout
class(psb_lbase_sparse_mat), intent(in) :: a class(psb_lbase_sparse_mat), intent(in) :: a
integer(psb_lpk_), intent(in), optional :: iv(:) integer(psb_lpk_), intent(in), optional :: iv(:)
character(len=*), optional :: head character(len=*), optional :: head

@ -592,7 +592,7 @@ subroutine psb_c_coo_clean_zeros(a, info)
use psb_c_base_mat_mod, psb_protect_name => psb_c_coo_clean_zeros use psb_c_base_mat_mod, psb_protect_name => psb_c_coo_clean_zeros
implicit none implicit none
class(psb_c_coo_sparse_mat), intent(inout) :: a class(psb_c_coo_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_ipk_) :: i,j,k, nzin integer(psb_ipk_) :: i,j,k, nzin
@ -5264,7 +5264,7 @@ subroutine psb_lc_coo_clean_zeros(a, info)
use psb_c_base_mat_mod, psb_protect_name => psb_lc_coo_clean_zeros use psb_c_base_mat_mod, psb_protect_name => psb_lc_coo_clean_zeros
implicit none implicit none
class(psb_lc_coo_sparse_mat), intent(inout) :: a class(psb_lc_coo_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_lpk_) :: i,j,k, nzin integer(psb_lpk_) :: i,j,k, nzin
@ -6760,7 +6760,8 @@ subroutine psb_lc_fix_coo_inner(nr,nc,nzin,dupl,ia,ja,val,nzout,info,idir)
use psb_sort_mod use psb_sort_mod
implicit none implicit none
integer(psb_lpk_), intent(in) :: nr, nc, nzin, dupl integer(psb_lpk_), intent(in) :: nr, nc, nzin
integer(psb_ipk_), intent(in) :: dupl
integer(psb_lpk_), intent(inout) :: ia(:), ja(:) integer(psb_lpk_), intent(inout) :: ia(:), ja(:)
complex(psb_spk_), intent(inout) :: val(:) complex(psb_spk_), intent(inout) :: val(:)
integer(psb_lpk_), intent(out) :: nzout integer(psb_lpk_), intent(out) :: nzout

@ -2371,7 +2371,7 @@ subroutine psb_c_csc_clean_zeros(a, info)
use psb_c_csc_mat_mod, psb_protect_name => psb_c_csc_clean_zeros use psb_c_csc_mat_mod, psb_protect_name => psb_c_csc_clean_zeros
implicit none implicit none
class(psb_c_csc_sparse_mat), intent(inout) :: a class(psb_c_csc_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_ipk_) :: i, j, k, nc integer(psb_ipk_) :: i, j, k, nc
integer(psb_ipk_), allocatable :: ilcp(:) integer(psb_ipk_), allocatable :: ilcp(:)
@ -4255,7 +4255,7 @@ subroutine psb_lc_csc_clean_zeros(a, info)
use psb_c_csc_mat_mod, psb_protect_name => psb_lc_csc_clean_zeros use psb_c_csc_mat_mod, psb_protect_name => psb_lc_csc_clean_zeros
implicit none implicit none
class(psb_lc_csc_sparse_mat), intent(inout) :: a class(psb_lc_csc_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_lpk_) :: i, j, k, nc integer(psb_lpk_) :: i, j, k, nc
integer(psb_lpk_), allocatable :: ilcp(:) integer(psb_lpk_), allocatable :: ilcp(:)
@ -4319,7 +4319,7 @@ subroutine psb_lc_csc_reallocate_nz(nz,a)
use psb_realloc_mod use psb_realloc_mod
use psb_c_csc_mat_mod, psb_protect_name => psb_lc_csc_reallocate_nz use psb_c_csc_mat_mod, psb_protect_name => psb_lc_csc_reallocate_nz
implicit none implicit none
integer(psb_ipk_), intent(in) :: nz integer(psb_lpk_), intent(in) :: nz
class(psb_lc_csc_sparse_mat), intent(inout) :: a class(psb_lc_csc_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: err_act, info, ierr(5) integer(psb_ipk_) :: err_act, info, ierr(5)
character(len=20) :: name='lc_csc_reallocate_nz' character(len=20) :: name='lc_csc_reallocate_nz'

@ -3235,7 +3235,7 @@ subroutine psb_c_csr_clean_zeros(a, info)
use psb_c_csr_mat_mod, psb_protect_name => psb_c_csr_clean_zeros use psb_c_csr_mat_mod, psb_protect_name => psb_c_csr_clean_zeros
implicit none implicit none
class(psb_c_csr_sparse_mat), intent(inout) :: a class(psb_c_csr_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_ipk_) :: i, j, k, nr integer(psb_ipk_) :: i, j, k, nr
integer(psb_ipk_), allocatable :: ilrp(:) integer(psb_ipk_), allocatable :: ilrp(:)
@ -5350,7 +5350,7 @@ subroutine psb_lc_csr_clean_zeros(a, info)
use psb_c_csr_mat_mod, psb_protect_name => psb_lc_csr_clean_zeros use psb_c_csr_mat_mod, psb_protect_name => psb_lc_csr_clean_zeros
implicit none implicit none
class(psb_lc_csr_sparse_mat), intent(inout) :: a class(psb_lc_csr_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_lpk_) :: i, j, k, nr integer(psb_lpk_) :: i, j, k, nr
integer(psb_lpk_), allocatable :: ilrp(:) integer(psb_lpk_), allocatable :: ilrp(:)

@ -592,7 +592,7 @@ subroutine psb_d_coo_clean_zeros(a, info)
use psb_d_base_mat_mod, psb_protect_name => psb_d_coo_clean_zeros use psb_d_base_mat_mod, psb_protect_name => psb_d_coo_clean_zeros
implicit none implicit none
class(psb_d_coo_sparse_mat), intent(inout) :: a class(psb_d_coo_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_ipk_) :: i,j,k, nzin integer(psb_ipk_) :: i,j,k, nzin
@ -5264,7 +5264,7 @@ subroutine psb_ld_coo_clean_zeros(a, info)
use psb_d_base_mat_mod, psb_protect_name => psb_ld_coo_clean_zeros use psb_d_base_mat_mod, psb_protect_name => psb_ld_coo_clean_zeros
implicit none implicit none
class(psb_ld_coo_sparse_mat), intent(inout) :: a class(psb_ld_coo_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_lpk_) :: i,j,k, nzin integer(psb_lpk_) :: i,j,k, nzin
@ -6760,7 +6760,8 @@ subroutine psb_ld_fix_coo_inner(nr,nc,nzin,dupl,ia,ja,val,nzout,info,idir)
use psb_sort_mod use psb_sort_mod
implicit none implicit none
integer(psb_lpk_), intent(in) :: nr, nc, nzin, dupl integer(psb_lpk_), intent(in) :: nr, nc, nzin
integer(psb_ipk_), intent(in) :: dupl
integer(psb_lpk_), intent(inout) :: ia(:), ja(:) integer(psb_lpk_), intent(inout) :: ia(:), ja(:)
real(psb_dpk_), intent(inout) :: val(:) real(psb_dpk_), intent(inout) :: val(:)
integer(psb_lpk_), intent(out) :: nzout integer(psb_lpk_), intent(out) :: nzout

@ -2371,7 +2371,7 @@ subroutine psb_d_csc_clean_zeros(a, info)
use psb_d_csc_mat_mod, psb_protect_name => psb_d_csc_clean_zeros use psb_d_csc_mat_mod, psb_protect_name => psb_d_csc_clean_zeros
implicit none implicit none
class(psb_d_csc_sparse_mat), intent(inout) :: a class(psb_d_csc_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_ipk_) :: i, j, k, nc integer(psb_ipk_) :: i, j, k, nc
integer(psb_ipk_), allocatable :: ilcp(:) integer(psb_ipk_), allocatable :: ilcp(:)
@ -4255,7 +4255,7 @@ subroutine psb_ld_csc_clean_zeros(a, info)
use psb_d_csc_mat_mod, psb_protect_name => psb_ld_csc_clean_zeros use psb_d_csc_mat_mod, psb_protect_name => psb_ld_csc_clean_zeros
implicit none implicit none
class(psb_ld_csc_sparse_mat), intent(inout) :: a class(psb_ld_csc_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_lpk_) :: i, j, k, nc integer(psb_lpk_) :: i, j, k, nc
integer(psb_lpk_), allocatable :: ilcp(:) integer(psb_lpk_), allocatable :: ilcp(:)
@ -4319,7 +4319,7 @@ subroutine psb_ld_csc_reallocate_nz(nz,a)
use psb_realloc_mod use psb_realloc_mod
use psb_d_csc_mat_mod, psb_protect_name => psb_ld_csc_reallocate_nz use psb_d_csc_mat_mod, psb_protect_name => psb_ld_csc_reallocate_nz
implicit none implicit none
integer(psb_ipk_), intent(in) :: nz integer(psb_lpk_), intent(in) :: nz
class(psb_ld_csc_sparse_mat), intent(inout) :: a class(psb_ld_csc_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: err_act, info, ierr(5) integer(psb_ipk_) :: err_act, info, ierr(5)
character(len=20) :: name='ld_csc_reallocate_nz' character(len=20) :: name='ld_csc_reallocate_nz'

@ -3235,7 +3235,7 @@ subroutine psb_d_csr_clean_zeros(a, info)
use psb_d_csr_mat_mod, psb_protect_name => psb_d_csr_clean_zeros use psb_d_csr_mat_mod, psb_protect_name => psb_d_csr_clean_zeros
implicit none implicit none
class(psb_d_csr_sparse_mat), intent(inout) :: a class(psb_d_csr_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_ipk_) :: i, j, k, nr integer(psb_ipk_) :: i, j, k, nr
integer(psb_ipk_), allocatable :: ilrp(:) integer(psb_ipk_), allocatable :: ilrp(:)
@ -5350,7 +5350,7 @@ subroutine psb_ld_csr_clean_zeros(a, info)
use psb_d_csr_mat_mod, psb_protect_name => psb_ld_csr_clean_zeros use psb_d_csr_mat_mod, psb_protect_name => psb_ld_csr_clean_zeros
implicit none implicit none
class(psb_ld_csr_sparse_mat), intent(inout) :: a class(psb_ld_csr_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_lpk_) :: i, j, k, nr integer(psb_lpk_) :: i, j, k, nr
integer(psb_lpk_), allocatable :: ilrp(:) integer(psb_lpk_), allocatable :: ilrp(:)

@ -592,7 +592,7 @@ subroutine psb_s_coo_clean_zeros(a, info)
use psb_s_base_mat_mod, psb_protect_name => psb_s_coo_clean_zeros use psb_s_base_mat_mod, psb_protect_name => psb_s_coo_clean_zeros
implicit none implicit none
class(psb_s_coo_sparse_mat), intent(inout) :: a class(psb_s_coo_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_ipk_) :: i,j,k, nzin integer(psb_ipk_) :: i,j,k, nzin
@ -5264,7 +5264,7 @@ subroutine psb_ls_coo_clean_zeros(a, info)
use psb_s_base_mat_mod, psb_protect_name => psb_ls_coo_clean_zeros use psb_s_base_mat_mod, psb_protect_name => psb_ls_coo_clean_zeros
implicit none implicit none
class(psb_ls_coo_sparse_mat), intent(inout) :: a class(psb_ls_coo_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_lpk_) :: i,j,k, nzin integer(psb_lpk_) :: i,j,k, nzin
@ -6760,7 +6760,8 @@ subroutine psb_ls_fix_coo_inner(nr,nc,nzin,dupl,ia,ja,val,nzout,info,idir)
use psb_sort_mod use psb_sort_mod
implicit none implicit none
integer(psb_lpk_), intent(in) :: nr, nc, nzin, dupl integer(psb_lpk_), intent(in) :: nr, nc, nzin
integer(psb_ipk_), intent(in) :: dupl
integer(psb_lpk_), intent(inout) :: ia(:), ja(:) integer(psb_lpk_), intent(inout) :: ia(:), ja(:)
real(psb_spk_), intent(inout) :: val(:) real(psb_spk_), intent(inout) :: val(:)
integer(psb_lpk_), intent(out) :: nzout integer(psb_lpk_), intent(out) :: nzout

@ -2371,7 +2371,7 @@ subroutine psb_s_csc_clean_zeros(a, info)
use psb_s_csc_mat_mod, psb_protect_name => psb_s_csc_clean_zeros use psb_s_csc_mat_mod, psb_protect_name => psb_s_csc_clean_zeros
implicit none implicit none
class(psb_s_csc_sparse_mat), intent(inout) :: a class(psb_s_csc_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_ipk_) :: i, j, k, nc integer(psb_ipk_) :: i, j, k, nc
integer(psb_ipk_), allocatable :: ilcp(:) integer(psb_ipk_), allocatable :: ilcp(:)
@ -4255,7 +4255,7 @@ subroutine psb_ls_csc_clean_zeros(a, info)
use psb_s_csc_mat_mod, psb_protect_name => psb_ls_csc_clean_zeros use psb_s_csc_mat_mod, psb_protect_name => psb_ls_csc_clean_zeros
implicit none implicit none
class(psb_ls_csc_sparse_mat), intent(inout) :: a class(psb_ls_csc_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_lpk_) :: i, j, k, nc integer(psb_lpk_) :: i, j, k, nc
integer(psb_lpk_), allocatable :: ilcp(:) integer(psb_lpk_), allocatable :: ilcp(:)
@ -4319,7 +4319,7 @@ subroutine psb_ls_csc_reallocate_nz(nz,a)
use psb_realloc_mod use psb_realloc_mod
use psb_s_csc_mat_mod, psb_protect_name => psb_ls_csc_reallocate_nz use psb_s_csc_mat_mod, psb_protect_name => psb_ls_csc_reallocate_nz
implicit none implicit none
integer(psb_ipk_), intent(in) :: nz integer(psb_lpk_), intent(in) :: nz
class(psb_ls_csc_sparse_mat), intent(inout) :: a class(psb_ls_csc_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: err_act, info, ierr(5) integer(psb_ipk_) :: err_act, info, ierr(5)
character(len=20) :: name='ls_csc_reallocate_nz' character(len=20) :: name='ls_csc_reallocate_nz'

@ -3235,7 +3235,7 @@ subroutine psb_s_csr_clean_zeros(a, info)
use psb_s_csr_mat_mod, psb_protect_name => psb_s_csr_clean_zeros use psb_s_csr_mat_mod, psb_protect_name => psb_s_csr_clean_zeros
implicit none implicit none
class(psb_s_csr_sparse_mat), intent(inout) :: a class(psb_s_csr_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_ipk_) :: i, j, k, nr integer(psb_ipk_) :: i, j, k, nr
integer(psb_ipk_), allocatable :: ilrp(:) integer(psb_ipk_), allocatable :: ilrp(:)
@ -5350,7 +5350,7 @@ subroutine psb_ls_csr_clean_zeros(a, info)
use psb_s_csr_mat_mod, psb_protect_name => psb_ls_csr_clean_zeros use psb_s_csr_mat_mod, psb_protect_name => psb_ls_csr_clean_zeros
implicit none implicit none
class(psb_ls_csr_sparse_mat), intent(inout) :: a class(psb_ls_csr_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_lpk_) :: i, j, k, nr integer(psb_lpk_) :: i, j, k, nr
integer(psb_lpk_), allocatable :: ilrp(:) integer(psb_lpk_), allocatable :: ilrp(:)

@ -592,7 +592,7 @@ subroutine psb_z_coo_clean_zeros(a, info)
use psb_z_base_mat_mod, psb_protect_name => psb_z_coo_clean_zeros use psb_z_base_mat_mod, psb_protect_name => psb_z_coo_clean_zeros
implicit none implicit none
class(psb_z_coo_sparse_mat), intent(inout) :: a class(psb_z_coo_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_ipk_) :: i,j,k, nzin integer(psb_ipk_) :: i,j,k, nzin
@ -5264,7 +5264,7 @@ subroutine psb_lz_coo_clean_zeros(a, info)
use psb_z_base_mat_mod, psb_protect_name => psb_lz_coo_clean_zeros use psb_z_base_mat_mod, psb_protect_name => psb_lz_coo_clean_zeros
implicit none implicit none
class(psb_lz_coo_sparse_mat), intent(inout) :: a class(psb_lz_coo_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_lpk_) :: i,j,k, nzin integer(psb_lpk_) :: i,j,k, nzin
@ -6760,7 +6760,8 @@ subroutine psb_lz_fix_coo_inner(nr,nc,nzin,dupl,ia,ja,val,nzout,info,idir)
use psb_sort_mod use psb_sort_mod
implicit none implicit none
integer(psb_lpk_), intent(in) :: nr, nc, nzin, dupl integer(psb_lpk_), intent(in) :: nr, nc, nzin
integer(psb_ipk_), intent(in) :: dupl
integer(psb_lpk_), intent(inout) :: ia(:), ja(:) integer(psb_lpk_), intent(inout) :: ia(:), ja(:)
complex(psb_dpk_), intent(inout) :: val(:) complex(psb_dpk_), intent(inout) :: val(:)
integer(psb_lpk_), intent(out) :: nzout integer(psb_lpk_), intent(out) :: nzout

@ -2371,7 +2371,7 @@ subroutine psb_z_csc_clean_zeros(a, info)
use psb_z_csc_mat_mod, psb_protect_name => psb_z_csc_clean_zeros use psb_z_csc_mat_mod, psb_protect_name => psb_z_csc_clean_zeros
implicit none implicit none
class(psb_z_csc_sparse_mat), intent(inout) :: a class(psb_z_csc_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_ipk_) :: i, j, k, nc integer(psb_ipk_) :: i, j, k, nc
integer(psb_ipk_), allocatable :: ilcp(:) integer(psb_ipk_), allocatable :: ilcp(:)
@ -4255,7 +4255,7 @@ subroutine psb_lz_csc_clean_zeros(a, info)
use psb_z_csc_mat_mod, psb_protect_name => psb_lz_csc_clean_zeros use psb_z_csc_mat_mod, psb_protect_name => psb_lz_csc_clean_zeros
implicit none implicit none
class(psb_lz_csc_sparse_mat), intent(inout) :: a class(psb_lz_csc_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_lpk_) :: i, j, k, nc integer(psb_lpk_) :: i, j, k, nc
integer(psb_lpk_), allocatable :: ilcp(:) integer(psb_lpk_), allocatable :: ilcp(:)
@ -4319,7 +4319,7 @@ subroutine psb_lz_csc_reallocate_nz(nz,a)
use psb_realloc_mod use psb_realloc_mod
use psb_z_csc_mat_mod, psb_protect_name => psb_lz_csc_reallocate_nz use psb_z_csc_mat_mod, psb_protect_name => psb_lz_csc_reallocate_nz
implicit none implicit none
integer(psb_ipk_), intent(in) :: nz integer(psb_lpk_), intent(in) :: nz
class(psb_lz_csc_sparse_mat), intent(inout) :: a class(psb_lz_csc_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: err_act, info, ierr(5) integer(psb_ipk_) :: err_act, info, ierr(5)
character(len=20) :: name='lz_csc_reallocate_nz' character(len=20) :: name='lz_csc_reallocate_nz'

@ -3235,7 +3235,7 @@ subroutine psb_z_csr_clean_zeros(a, info)
use psb_z_csr_mat_mod, psb_protect_name => psb_z_csr_clean_zeros use psb_z_csr_mat_mod, psb_protect_name => psb_z_csr_clean_zeros
implicit none implicit none
class(psb_z_csr_sparse_mat), intent(inout) :: a class(psb_z_csr_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_ipk_) :: i, j, k, nr integer(psb_ipk_) :: i, j, k, nr
integer(psb_ipk_), allocatable :: ilrp(:) integer(psb_ipk_), allocatable :: ilrp(:)
@ -5350,7 +5350,7 @@ subroutine psb_lz_csr_clean_zeros(a, info)
use psb_z_csr_mat_mod, psb_protect_name => psb_lz_csr_clean_zeros use psb_z_csr_mat_mod, psb_protect_name => psb_lz_csr_clean_zeros
implicit none implicit none
class(psb_lz_csr_sparse_mat), intent(inout) :: a class(psb_lz_csr_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: info integer(psb_ipk_), intent(out) :: info
! !
integer(psb_lpk_) :: i, j, k, nr integer(psb_lpk_) :: i, j, k, nr
integer(psb_lpk_), allocatable :: ilrp(:) integer(psb_lpk_), allocatable :: ilrp(:)

Loading…
Cancel
Save