base/modules/psb_c_base_mat_mod.f90
 base/modules/psb_c_linmap_mod.f90
 base/modules/psb_c_mat_mod.f90
 base/modules/psb_c_vect_mod.F90
 base/modules/psb_d_base_mat_mod.f90
 base/modules/psb_d_linmap_mod.f90
 base/modules/psb_d_mat_mod.f90
 base/modules/psb_d_vect_mod.F90
 base/modules/psb_i_vect_mod.F90
 base/modules/psb_s_base_mat_mod.f90
 base/modules/psb_s_linmap_mod.f90
 base/modules/psb_s_mat_mod.f90
 base/modules/psb_s_vect_mod.F90
 base/modules/psb_z_base_mat_mod.f90
 base/modules/psb_z_linmap_mod.f90
 base/modules/psb_z_mat_mod.f90
 base/modules/psb_z_vect_mod.F90
 base/serial/impl/psb_c_base_mat_impl.F90
 base/serial/impl/psb_c_mat_impl.F90
 base/serial/impl/psb_d_base_mat_impl.F90
 base/serial/impl/psb_d_mat_impl.F90
 base/serial/impl/psb_s_base_mat_impl.F90
 base/serial/impl/psb_s_mat_impl.F90
 base/serial/impl/psb_z_base_mat_impl.F90
 base/serial/impl/psb_z_mat_impl.F90
 base/tools/psb_c_map.f90
 base/tools/psb_d_map.f90
 base/tools/psb_s_map.f90
 base/tools/psb_z_map.f90


Reimplement CLONE for sparse matrices, base on CLONE for inner class.
Define CLONE method for map.
psblas3-final
Salvatore Filippone 12 years ago
parent cfb2f9ffa8
commit c87ecdb770

@ -76,6 +76,7 @@ module psb_c_base_mat_mod
generic, public :: cp_from => c_base_cp_from
procedure, pass(a) :: c_base_mv_from
generic, public :: mv_from => c_base_mv_from
procedure, pass(a) :: clone => psb_c_base_clone
!
! Transpose methods: defined here but not implemented.
@ -112,7 +113,7 @@ module psb_c_base_mat_mod
procedure, pass(a) :: aclsum => psb_c_base_aclsum
end type psb_c_base_sparse_mat
private :: base_cp_from, base_mv_from
private :: c_base_cp_from, c_base_mv_from
!> \namespace psb_base_mod \class psb_c_coo_sparse_mat
@ -413,10 +414,30 @@ module psb_c_base_mat_mod
import :: psb_ipk_, psb_c_base_sparse_mat, psb_long_int_k_
class(psb_c_base_sparse_mat), intent(in) :: a
class(psb_c_base_sparse_mat), intent(out), allocatable :: b
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(out) :: info
end subroutine psb_c_base_mold
end interface
!
!> Function clone:
!! \memberof psb_c_base_sparse_mat
!! \brief Allocate and clone a class(psb_c_base_sparse_mat) with the
!! same dynamic type as the input.
!! This is equivalent to allocate( source= ) except that
!! it should guarantee a deep copy wherever needed.
!! \param b The output variable
!! \param info return code
!
interface
subroutine psb_c_base_clone(a,b, info)
import :: psb_ipk_, psb_c_base_sparse_mat, psb_long_int_k_
implicit none
class(psb_c_base_sparse_mat), intent(inout) :: a
class(psb_c_base_sparse_mat), allocatable, intent(out) :: b
integer(psb_ipk_), intent(out) :: info
end subroutine psb_c_base_clone
end interface
!
!> Function cp_to_coo:
@ -1565,6 +1586,7 @@ module psb_c_base_mat_mod
contains
subroutine c_base_mv_from(a,b)
implicit none

@ -46,9 +46,10 @@ module psb_c_linmap_mod
type, extends(psb_base_linmap_type) :: psb_clinmap_type
type(psb_cspmat_type) :: map_X2Y, map_Y2X
contains
procedure, pass(map) :: sizeof => c_map_sizeof
procedure, pass(map) :: is_asb => c_is_asb
procedure, pass(map) :: free => c_free
procedure, pass(map) :: sizeof => c_map_sizeof
procedure, pass(map) :: is_asb => c_is_asb
procedure, pass(map) :: free => c_free
procedure, pass(mapin) :: clone => c_clone
end type psb_clinmap_type
@ -116,11 +117,11 @@ module psb_c_linmap_mod
use psb_c_mat_mod, only : psb_cspmat_type
import :: psb_ipk_, psb_clinmap_type, psb_desc_type
implicit none
type(psb_clinmap_type) :: psb_c_linmap
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_cspmat_type), intent(in) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
type(psb_clinmap_type) :: psb_c_linmap
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_cspmat_type), intent(inout) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
end function psb_c_linmap
end interface
@ -176,11 +177,11 @@ contains
& map_X2Y, map_Y2X,iaggr,naggr)
use psb_c_mat_mod
implicit none
type(psb_clinmap_type), intent(out) :: out_map
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_cspmat_type), intent(in) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
type(psb_clinmap_type), intent(out) :: out_map
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_cspmat_type), intent(inout) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
out_map = psb_linmap(map_kind,desc_X,desc_Y,map_X2Y,map_Y2X,iaggr,naggr)
end subroutine psb_c_linmap_sub
@ -213,5 +214,19 @@ contains
end subroutine c_free
subroutine c_clone(mapin,mapout)
use psb_desc_mod
implicit none
class(psb_clinmap_type), intent(inout) :: mapin
class(psb_clinmap_type), intent(out) :: mapout
integer(psb_ipk_) :: info
! Base clone!
call mapin%map_X2Y%clone(mapout%map_X2Y,info)
call mapin%map_Y2X%clone(mapout%map_Y2X,info)
end subroutine c_clone
end module psb_c_linmap_mod

@ -612,9 +612,9 @@ module psb_c_mat_mod
interface
subroutine psb_cspmat_clone(a,b,info)
import :: psb_ipk_, psb_cspmat_type
class(psb_cspmat_type), intent(in) :: a
class(psb_cspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
class(psb_cspmat_type), intent(inout) :: a
class(psb_cspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
end subroutine psb_cspmat_clone
end interface

@ -83,6 +83,7 @@ module psb_c_vect_mod
procedure, pass(x) :: set_scal => c_vect_set_scal
procedure, pass(x) :: set_vect => c_vect_set_vect
generic, public :: set => set_vect, set_scal
procedure, pass(x) :: clone => c_vect_clone
end type psb_c_vect_type
public :: psb_c_vect
@ -93,6 +94,17 @@ module psb_c_vect_mod
contains
subroutine c_vect_clone(x,y)
implicit none
class(psb_c_vect_type), intent(inout) :: x
class(psb_c_vect_type), intent(out) :: y
if (allocated(x%v)) then
call y%bld(x%get_vect(),mold=x%v)
end if
end subroutine c_vect_clone
subroutine c_vect_bld_x(x,invect,mold)
complex(psb_spk_), intent(in) :: invect(:)
class(psb_c_vect_type), intent(out) :: x

@ -76,6 +76,7 @@ module psb_d_base_mat_mod
generic, public :: cp_from => d_base_cp_from
procedure, pass(a) :: d_base_mv_from
generic, public :: mv_from => d_base_mv_from
procedure, pass(a) :: clone => psb_d_base_clone
!
! Transpose methods: defined here but not implemented.
@ -112,7 +113,7 @@ module psb_d_base_mat_mod
procedure, pass(a) :: aclsum => psb_d_base_aclsum
end type psb_d_base_sparse_mat
private :: base_cp_from, base_mv_from
private :: d_base_cp_from, d_base_mv_from
!> \namespace psb_base_mod \class psb_d_coo_sparse_mat
@ -413,10 +414,30 @@ module psb_d_base_mat_mod
import :: psb_ipk_, psb_d_base_sparse_mat, psb_long_int_k_
class(psb_d_base_sparse_mat), intent(in) :: a
class(psb_d_base_sparse_mat), intent(out), allocatable :: b
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(out) :: info
end subroutine psb_d_base_mold
end interface
!
!> Function clone:
!! \memberof psb_d_base_sparse_mat
!! \brief Allocate and clone a class(psb_d_base_sparse_mat) with the
!! same dynamic type as the input.
!! This is equivalent to allocate( source= ) except that
!! it should guarantee a deep copy wherever needed.
!! \param b The output variable
!! \param info return code
!
interface
subroutine psb_d_base_clone(a,b, info)
import :: psb_ipk_, psb_d_base_sparse_mat, psb_long_int_k_
implicit none
class(psb_d_base_sparse_mat), intent(inout) :: a
class(psb_d_base_sparse_mat), allocatable, intent(out) :: b
integer(psb_ipk_), intent(out) :: info
end subroutine psb_d_base_clone
end interface
!
!> Function cp_to_coo:
@ -1565,6 +1586,7 @@ module psb_d_base_mat_mod
contains
subroutine d_base_mv_from(a,b)
implicit none

@ -46,9 +46,10 @@ module psb_d_linmap_mod
type, extends(psb_base_linmap_type) :: psb_dlinmap_type
type(psb_dspmat_type) :: map_X2Y, map_Y2X
contains
procedure, pass(map) :: sizeof => d_map_sizeof
procedure, pass(map) :: is_asb => d_is_asb
procedure, pass(map) :: free => d_free
procedure, pass(map) :: sizeof => d_map_sizeof
procedure, pass(map) :: is_asb => d_is_asb
procedure, pass(map) :: free => d_free
procedure, pass(mapin) :: clone => d_clone
end type psb_dlinmap_type
@ -116,11 +117,11 @@ module psb_d_linmap_mod
use psb_d_mat_mod, only : psb_dspmat_type
import :: psb_ipk_, psb_dlinmap_type, psb_desc_type
implicit none
type(psb_dlinmap_type) :: psb_d_linmap
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_dspmat_type), intent(in) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
type(psb_dlinmap_type) :: psb_d_linmap
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_dspmat_type), intent(inout) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
end function psb_d_linmap
end interface
@ -176,11 +177,11 @@ contains
& map_X2Y, map_Y2X,iaggr,naggr)
use psb_d_mat_mod
implicit none
type(psb_dlinmap_type), intent(out) :: out_map
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_dspmat_type), intent(in) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
type(psb_dlinmap_type), intent(out) :: out_map
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_dspmat_type), intent(inout) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
out_map = psb_linmap(map_kind,desc_X,desc_Y,map_X2Y,map_Y2X,iaggr,naggr)
end subroutine psb_d_linmap_sub
@ -213,5 +214,19 @@ contains
end subroutine d_free
subroutine d_clone(mapin,mapout)
use psb_desc_mod
implicit none
class(psb_dlinmap_type), intent(inout) :: mapin
class(psb_dlinmap_type), intent(out) :: mapout
integer(psb_ipk_) :: info
! Base clone!
call mapin%map_X2Y%clone(mapout%map_X2Y,info)
call mapin%map_Y2X%clone(mapout%map_Y2X,info)
end subroutine d_clone
end module psb_d_linmap_mod

@ -612,9 +612,9 @@ module psb_d_mat_mod
interface
subroutine psb_dspmat_clone(a,b,info)
import :: psb_ipk_, psb_dspmat_type
class(psb_dspmat_type), intent(in) :: a
class(psb_dspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
class(psb_dspmat_type), intent(inout) :: a
class(psb_dspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
end subroutine psb_dspmat_clone
end interface

@ -83,6 +83,7 @@ module psb_d_vect_mod
procedure, pass(x) :: set_scal => d_vect_set_scal
procedure, pass(x) :: set_vect => d_vect_set_vect
generic, public :: set => set_vect, set_scal
procedure, pass(x) :: clone => d_vect_clone
end type psb_d_vect_type
public :: psb_d_vect
@ -93,6 +94,17 @@ module psb_d_vect_mod
contains
subroutine d_vect_clone(x,y)
implicit none
class(psb_d_vect_type), intent(inout) :: x
class(psb_d_vect_type), intent(out) :: y
if (allocated(x%v)) then
call y%bld(x%get_vect(),mold=x%v)
end if
end subroutine d_vect_clone
subroutine d_vect_bld_x(x,invect,mold)
real(psb_dpk_), intent(in) :: invect(:)
class(psb_d_vect_type), intent(out) :: x

@ -83,6 +83,7 @@ module psb_i_vect_mod
procedure, pass(x) :: set_scal => i_vect_set_scal
procedure, pass(x) :: set_vect => i_vect_set_vect
generic, public :: set => set_vect, set_scal
procedure, pass(x) :: clone => i_vect_clone
end type psb_i_vect_type
public :: psb_i_vect
@ -93,6 +94,17 @@ module psb_i_vect_mod
contains
subroutine i_vect_clone(x,y)
implicit none
class(psb_i_vect_type), intent(inout) :: x
class(psb_i_vect_type), intent(out) :: y
if (allocated(x%v)) then
call y%bld(x%get_vect(),mold=x%v)
end if
end subroutine i_vect_clone
subroutine i_vect_bld_x(x,invect,mold)
integer(psb_ipk_), intent(in) :: invect(:)
class(psb_i_vect_type), intent(out) :: x

@ -76,6 +76,7 @@ module psb_s_base_mat_mod
generic, public :: cp_from => s_base_cp_from
procedure, pass(a) :: s_base_mv_from
generic, public :: mv_from => s_base_mv_from
procedure, pass(a) :: clone => psb_s_base_clone
!
! Transpose methods: defined here but not implemented.
@ -112,7 +113,7 @@ module psb_s_base_mat_mod
procedure, pass(a) :: aclsum => psb_s_base_aclsum
end type psb_s_base_sparse_mat
private :: base_cp_from, base_mv_from
private :: s_base_cp_from, s_base_mv_from
!> \namespace psb_base_mod \class psb_s_coo_sparse_mat
@ -413,10 +414,30 @@ module psb_s_base_mat_mod
import :: psb_ipk_, psb_s_base_sparse_mat, psb_long_int_k_
class(psb_s_base_sparse_mat), intent(in) :: a
class(psb_s_base_sparse_mat), intent(out), allocatable :: b
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(out) :: info
end subroutine psb_s_base_mold
end interface
!
!> Function clone:
!! \memberof psb_s_base_sparse_mat
!! \brief Allocate and clone a class(psb_s_base_sparse_mat) with the
!! same dynamic type as the input.
!! This is equivalent to allocate( source= ) except that
!! it should guarantee a deep copy wherever needed.
!! \param b The output variable
!! \param info return code
!
interface
subroutine psb_s_base_clone(a,b, info)
import :: psb_ipk_, psb_s_base_sparse_mat, psb_long_int_k_
implicit none
class(psb_s_base_sparse_mat), intent(inout) :: a
class(psb_s_base_sparse_mat), allocatable, intent(out) :: b
integer(psb_ipk_), intent(out) :: info
end subroutine psb_s_base_clone
end interface
!
!> Function cp_to_coo:
@ -1565,6 +1586,7 @@ module psb_s_base_mat_mod
contains
subroutine s_base_mv_from(a,b)
implicit none

@ -46,9 +46,10 @@ module psb_s_linmap_mod
type, extends(psb_base_linmap_type) :: psb_slinmap_type
type(psb_sspmat_type) :: map_X2Y, map_Y2X
contains
procedure, pass(map) :: sizeof => s_map_sizeof
procedure, pass(map) :: is_asb => s_is_asb
procedure, pass(map) :: free => s_free
procedure, pass(map) :: sizeof => s_map_sizeof
procedure, pass(map) :: is_asb => s_is_asb
procedure, pass(map) :: free => s_free
procedure, pass(mapin) :: clone => s_clone
end type psb_slinmap_type
@ -116,11 +117,11 @@ module psb_s_linmap_mod
use psb_s_mat_mod, only : psb_sspmat_type
import :: psb_ipk_, psb_slinmap_type, psb_desc_type
implicit none
type(psb_slinmap_type) :: psb_s_linmap
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_sspmat_type), intent(in) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
type(psb_slinmap_type) :: psb_s_linmap
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_sspmat_type), intent(inout) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
end function psb_s_linmap
end interface
@ -176,11 +177,11 @@ contains
& map_X2Y, map_Y2X,iaggr,naggr)
use psb_s_mat_mod
implicit none
type(psb_slinmap_type), intent(out) :: out_map
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_sspmat_type), intent(in) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
type(psb_slinmap_type), intent(out) :: out_map
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_sspmat_type), intent(inout) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
out_map = psb_linmap(map_kind,desc_X,desc_Y,map_X2Y,map_Y2X,iaggr,naggr)
end subroutine psb_s_linmap_sub
@ -213,5 +214,19 @@ contains
end subroutine s_free
subroutine s_clone(mapin,mapout)
use psb_desc_mod
implicit none
class(psb_slinmap_type), intent(inout) :: mapin
class(psb_slinmap_type), intent(out) :: mapout
integer(psb_ipk_) :: info
! Base clone!
call mapin%map_X2Y%clone(mapout%map_X2Y,info)
call mapin%map_Y2X%clone(mapout%map_Y2X,info)
end subroutine s_clone
end module psb_s_linmap_mod

@ -612,9 +612,9 @@ module psb_s_mat_mod
interface
subroutine psb_sspmat_clone(a,b,info)
import :: psb_ipk_, psb_sspmat_type
class(psb_sspmat_type), intent(in) :: a
class(psb_sspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
class(psb_sspmat_type), intent(inout) :: a
class(psb_sspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
end subroutine psb_sspmat_clone
end interface

@ -83,6 +83,7 @@ module psb_s_vect_mod
procedure, pass(x) :: set_scal => s_vect_set_scal
procedure, pass(x) :: set_vect => s_vect_set_vect
generic, public :: set => set_vect, set_scal
procedure, pass(x) :: clone => s_vect_clone
end type psb_s_vect_type
public :: psb_s_vect
@ -93,6 +94,17 @@ module psb_s_vect_mod
contains
subroutine s_vect_clone(x,y)
implicit none
class(psb_s_vect_type), intent(inout) :: x
class(psb_s_vect_type), intent(out) :: y
if (allocated(x%v)) then
call y%bld(x%get_vect(),mold=x%v)
end if
end subroutine s_vect_clone
subroutine s_vect_bld_x(x,invect,mold)
real(psb_spk_), intent(in) :: invect(:)
class(psb_s_vect_type), intent(out) :: x

@ -76,6 +76,7 @@ module psb_z_base_mat_mod
generic, public :: cp_from => z_base_cp_from
procedure, pass(a) :: z_base_mv_from
generic, public :: mv_from => z_base_mv_from
procedure, pass(a) :: clone => psb_z_base_clone
!
! Transpose methods: defined here but not implemented.
@ -112,7 +113,7 @@ module psb_z_base_mat_mod
procedure, pass(a) :: aclsum => psb_z_base_aclsum
end type psb_z_base_sparse_mat
private :: base_cp_from, base_mv_from
private :: z_base_cp_from, z_base_mv_from
!> \namespace psb_base_mod \class psb_z_coo_sparse_mat
@ -413,10 +414,30 @@ module psb_z_base_mat_mod
import :: psb_ipk_, psb_z_base_sparse_mat, psb_long_int_k_
class(psb_z_base_sparse_mat), intent(in) :: a
class(psb_z_base_sparse_mat), intent(out), allocatable :: b
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(out) :: info
end subroutine psb_z_base_mold
end interface
!
!> Function clone:
!! \memberof psb_z_base_sparse_mat
!! \brief Allocate and clone a class(psb_z_base_sparse_mat) with the
!! same dynamic type as the input.
!! This is equivalent to allocate( source= ) except that
!! it should guarantee a deep copy wherever needed.
!! \param b The output variable
!! \param info return code
!
interface
subroutine psb_z_base_clone(a,b, info)
import :: psb_ipk_, psb_z_base_sparse_mat, psb_long_int_k_
implicit none
class(psb_z_base_sparse_mat), intent(inout) :: a
class(psb_z_base_sparse_mat), allocatable, intent(out) :: b
integer(psb_ipk_), intent(out) :: info
end subroutine psb_z_base_clone
end interface
!
!> Function cp_to_coo:
@ -1565,6 +1586,7 @@ module psb_z_base_mat_mod
contains
subroutine z_base_mv_from(a,b)
implicit none

@ -46,9 +46,10 @@ module psb_z_linmap_mod
type, extends(psb_base_linmap_type) :: psb_zlinmap_type
type(psb_zspmat_type) :: map_X2Y, map_Y2X
contains
procedure, pass(map) :: sizeof => z_map_sizeof
procedure, pass(map) :: is_asb => z_is_asb
procedure, pass(map) :: free => z_free
procedure, pass(map) :: sizeof => z_map_sizeof
procedure, pass(map) :: is_asb => z_is_asb
procedure, pass(map) :: free => z_free
procedure, pass(mapin) :: clone => z_clone
end type psb_zlinmap_type
@ -116,11 +117,11 @@ module psb_z_linmap_mod
use psb_z_mat_mod, only : psb_zspmat_type
import :: psb_ipk_, psb_zlinmap_type, psb_desc_type
implicit none
type(psb_zlinmap_type) :: psb_z_linmap
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_zspmat_type), intent(in) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
type(psb_zlinmap_type) :: psb_z_linmap
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_zspmat_type), intent(inout) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
end function psb_z_linmap
end interface
@ -176,11 +177,11 @@ contains
& map_X2Y, map_Y2X,iaggr,naggr)
use psb_z_mat_mod
implicit none
type(psb_zlinmap_type), intent(out) :: out_map
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_zspmat_type), intent(in) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
type(psb_zlinmap_type), intent(out) :: out_map
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_zspmat_type), intent(inout) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
out_map = psb_linmap(map_kind,desc_X,desc_Y,map_X2Y,map_Y2X,iaggr,naggr)
end subroutine psb_z_linmap_sub
@ -213,5 +214,19 @@ contains
end subroutine z_free
subroutine z_clone(mapin,mapout)
use psb_desc_mod
implicit none
class(psb_zlinmap_type), intent(inout) :: mapin
class(psb_zlinmap_type), intent(out) :: mapout
integer(psb_ipk_) :: info
! Base clone!
call mapin%map_X2Y%clone(mapout%map_X2Y,info)
call mapin%map_Y2X%clone(mapout%map_Y2X,info)
end subroutine z_clone
end module psb_z_linmap_mod

@ -612,9 +612,9 @@ module psb_z_mat_mod
interface
subroutine psb_zspmat_clone(a,b,info)
import :: psb_ipk_, psb_zspmat_type
class(psb_zspmat_type), intent(in) :: a
class(psb_zspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
class(psb_zspmat_type), intent(inout) :: a
class(psb_zspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
end subroutine psb_zspmat_clone
end interface

@ -83,6 +83,7 @@ module psb_z_vect_mod
procedure, pass(x) :: set_scal => z_vect_set_scal
procedure, pass(x) :: set_vect => z_vect_set_vect
generic, public :: set => set_vect, set_scal
procedure, pass(x) :: clone => z_vect_clone
end type psb_z_vect_type
public :: psb_z_vect
@ -93,6 +94,17 @@ module psb_z_vect_mod
contains
subroutine z_vect_clone(x,y)
implicit none
class(psb_z_vect_type), intent(inout) :: x
class(psb_z_vect_type), intent(out) :: y
if (allocated(x%v)) then
call y%bld(x%get_vect(),mold=x%v)
end if
end subroutine z_vect_clone
subroutine z_vect_bld_x(x,invect,mold)
complex(psb_dpk_), intent(in) :: invect(:)
class(psb_z_vect_type), intent(out) :: x

@ -550,6 +550,25 @@ subroutine psb_c_base_csclip(a,b,info,&
end subroutine psb_c_base_csclip
subroutine psb_c_base_clone(a,b,info)
use psb_c_base_mat_mod, psb_protect_name => psb_c_base_clone
use psb_error_mod
implicit none
class(psb_c_base_sparse_mat), intent(inout) :: a
class(psb_c_base_sparse_mat), allocatable, intent(out) :: b
integer(psb_ipk_), intent(out) :: info
#if defined(HAVE_MOLD)
allocate(b,mold=a,stat=info)
if (info /= psb_success_) info = psb_err_alloc_dealloc_
#else
call a%mold(b,info)
#endif
if (info == psb_success_) call b%cp_from_fmt(a, info)
end subroutine psb_c_base_clone
subroutine psb_c_base_mold(a,b,info)
use psb_c_base_mat_mod, psb_protect_name => psb_c_base_mold
use psb_error_mod

@ -1444,7 +1444,7 @@ subroutine psb_c_cp_from(a,b)
class(psb_cspmat_type), intent(out) :: a
class(psb_c_base_sparse_mat), intent(in) :: b
integer(psb_ipk_) :: err_act, info
character(len=20) :: name='clone'
character(len=20) :: name='cp_from'
logical, parameter :: debug=.false.
call psb_erractionsave(err_act)
@ -1544,9 +1544,9 @@ subroutine psb_cspmat_clone(a,b,info)
use psb_string_mod
use psb_c_mat_mod, psb_protect_name => psb_cspmat_clone
implicit none
class(psb_cspmat_type), intent(in) :: a
class(psb_cspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
class(psb_cspmat_type), intent(inout) :: a
class(psb_cspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act
character(len=20) :: name='clone'
@ -1555,13 +1555,9 @@ subroutine psb_cspmat_clone(a,b,info)
call psb_erractionsave(err_act)
info = psb_success_
#if defined(HAVE_MOLD)
allocate(b%a,mold=a%a,stat=info)
if (info /= psb_success_) info = psb_err_alloc_dealloc_
#else
call a%a%mold(b%a,info)
#endif
if (info == psb_success_) call b%a%cp_from_fmt(a%a, info)
if (allocated(a%a)) then
call a%a%clone(b%a,info)
end if
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act)

@ -550,6 +550,25 @@ subroutine psb_d_base_csclip(a,b,info,&
end subroutine psb_d_base_csclip
subroutine psb_d_base_clone(a,b,info)
use psb_d_base_mat_mod, psb_protect_name => psb_d_base_clone
use psb_error_mod
implicit none
class(psb_d_base_sparse_mat), intent(inout) :: a
class(psb_d_base_sparse_mat), allocatable, intent(out) :: b
integer(psb_ipk_), intent(out) :: info
#if defined(HAVE_MOLD)
allocate(b,mold=a,stat=info)
if (info /= psb_success_) info = psb_err_alloc_dealloc_
#else
call a%mold(b,info)
#endif
if (info == psb_success_) call b%cp_from_fmt(a, info)
end subroutine psb_d_base_clone
subroutine psb_d_base_mold(a,b,info)
use psb_d_base_mat_mod, psb_protect_name => psb_d_base_mold
use psb_error_mod

@ -1444,7 +1444,7 @@ subroutine psb_d_cp_from(a,b)
class(psb_dspmat_type), intent(out) :: a
class(psb_d_base_sparse_mat), intent(in) :: b
integer(psb_ipk_) :: err_act, info
character(len=20) :: name='clone'
character(len=20) :: name='cp_from'
logical, parameter :: debug=.false.
call psb_erractionsave(err_act)
@ -1544,9 +1544,9 @@ subroutine psb_dspmat_clone(a,b,info)
use psb_string_mod
use psb_d_mat_mod, psb_protect_name => psb_dspmat_clone
implicit none
class(psb_dspmat_type), intent(in) :: a
class(psb_dspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
class(psb_dspmat_type), intent(inout) :: a
class(psb_dspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act
character(len=20) :: name='clone'
@ -1555,13 +1555,9 @@ subroutine psb_dspmat_clone(a,b,info)
call psb_erractionsave(err_act)
info = psb_success_
#if defined(HAVE_MOLD)
allocate(b%a,mold=a%a,stat=info)
if (info /= psb_success_) info = psb_err_alloc_dealloc_
#else
call a%a%mold(b%a,info)
#endif
if (info == psb_success_) call b%a%cp_from_fmt(a%a, info)
if (allocated(a%a)) then
call a%a%clone(b%a,info)
end if
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act)

@ -550,6 +550,25 @@ subroutine psb_s_base_csclip(a,b,info,&
end subroutine psb_s_base_csclip
subroutine psb_s_base_clone(a,b,info)
use psb_s_base_mat_mod, psb_protect_name => psb_s_base_clone
use psb_error_mod
implicit none
class(psb_s_base_sparse_mat), intent(inout) :: a
class(psb_s_base_sparse_mat), allocatable, intent(out) :: b
integer(psb_ipk_), intent(out) :: info
#if defined(HAVE_MOLD)
allocate(b,mold=a,stat=info)
if (info /= psb_success_) info = psb_err_alloc_dealloc_
#else
call a%mold(b,info)
#endif
if (info == psb_success_) call b%cp_from_fmt(a, info)
end subroutine psb_s_base_clone
subroutine psb_s_base_mold(a,b,info)
use psb_s_base_mat_mod, psb_protect_name => psb_s_base_mold
use psb_error_mod

@ -1444,7 +1444,7 @@ subroutine psb_s_cp_from(a,b)
class(psb_sspmat_type), intent(out) :: a
class(psb_s_base_sparse_mat), intent(in) :: b
integer(psb_ipk_) :: err_act, info
character(len=20) :: name='clone'
character(len=20) :: name='cp_from'
logical, parameter :: debug=.false.
call psb_erractionsave(err_act)
@ -1544,9 +1544,9 @@ subroutine psb_sspmat_clone(a,b,info)
use psb_string_mod
use psb_s_mat_mod, psb_protect_name => psb_sspmat_clone
implicit none
class(psb_sspmat_type), intent(in) :: a
class(psb_sspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
class(psb_sspmat_type), intent(inout) :: a
class(psb_sspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act
character(len=20) :: name='clone'
@ -1555,13 +1555,9 @@ subroutine psb_sspmat_clone(a,b,info)
call psb_erractionsave(err_act)
info = psb_success_
#if defined(HAVE_MOLD)
allocate(b%a,mold=a%a,stat=info)
if (info /= psb_success_) info = psb_err_alloc_dealloc_
#else
call a%a%mold(b%a,info)
#endif
if (info == psb_success_) call b%a%cp_from_fmt(a%a, info)
if (allocated(a%a)) then
call a%a%clone(b%a,info)
end if
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act)

@ -550,6 +550,25 @@ subroutine psb_z_base_csclip(a,b,info,&
end subroutine psb_z_base_csclip
subroutine psb_z_base_clone(a,b,info)
use psb_z_base_mat_mod, psb_protect_name => psb_z_base_clone
use psb_error_mod
implicit none
class(psb_z_base_sparse_mat), intent(inout) :: a
class(psb_z_base_sparse_mat), allocatable, intent(out) :: b
integer(psb_ipk_), intent(out) :: info
#if defined(HAVE_MOLD)
allocate(b,mold=a,stat=info)
if (info /= psb_success_) info = psb_err_alloc_dealloc_
#else
call a%mold(b,info)
#endif
if (info == psb_success_) call b%cp_from_fmt(a, info)
end subroutine psb_z_base_clone
subroutine psb_z_base_mold(a,b,info)
use psb_z_base_mat_mod, psb_protect_name => psb_z_base_mold
use psb_error_mod

@ -1444,7 +1444,7 @@ subroutine psb_z_cp_from(a,b)
class(psb_zspmat_type), intent(out) :: a
class(psb_z_base_sparse_mat), intent(in) :: b
integer(psb_ipk_) :: err_act, info
character(len=20) :: name='clone'
character(len=20) :: name='cp_from'
logical, parameter :: debug=.false.
call psb_erractionsave(err_act)
@ -1544,9 +1544,9 @@ subroutine psb_zspmat_clone(a,b,info)
use psb_string_mod
use psb_z_mat_mod, psb_protect_name => psb_zspmat_clone
implicit none
class(psb_zspmat_type), intent(in) :: a
class(psb_zspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
class(psb_zspmat_type), intent(inout) :: a
class(psb_zspmat_type), intent(out) :: b
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act
character(len=20) :: name='clone'
@ -1555,13 +1555,9 @@ subroutine psb_zspmat_clone(a,b,info)
call psb_erractionsave(err_act)
info = psb_success_
#if defined(HAVE_MOLD)
allocate(b%a,mold=a%a,stat=info)
if (info /= psb_success_) info = psb_err_alloc_dealloc_
#else
call a%a%mold(b%a,info)
#endif
if (info == psb_success_) call b%a%cp_from_fmt(a%a, info)
if (allocated(a%a)) then
call a%a%clone(b%a,info)
end if
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act)

@ -362,7 +362,7 @@ function psb_c_linmap(map_kind,desc_X, desc_Y, map_X2Y, map_Y2X,iaggr,naggr) &
implicit none
type(psb_clinmap_type) :: this
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_cspmat_type), intent(in) :: map_X2Y, map_Y2X
type(psb_cspmat_type), intent(inout) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
!

@ -362,7 +362,7 @@ function psb_d_linmap(map_kind,desc_X, desc_Y, map_X2Y, map_Y2X,iaggr,naggr) &
implicit none
type(psb_dlinmap_type) :: this
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_dspmat_type), intent(in) :: map_X2Y, map_Y2X
type(psb_dspmat_type), intent(inout) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
!

@ -362,7 +362,7 @@ function psb_s_linmap(map_kind,desc_X, desc_Y, map_X2Y, map_Y2X,iaggr,naggr) &
implicit none
type(psb_slinmap_type) :: this
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_sspmat_type), intent(in) :: map_X2Y, map_Y2X
type(psb_sspmat_type), intent(inout) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
!

@ -362,7 +362,7 @@ function psb_z_linmap(map_kind,desc_X, desc_Y, map_X2Y, map_Y2X,iaggr,naggr) &
implicit none
type(psb_zlinmap_type) :: this
type(psb_desc_type), target :: desc_X, desc_Y
type(psb_zspmat_type), intent(in) :: map_X2Y, map_Y2X
type(psb_zspmat_type), intent(inout) :: map_X2Y, map_Y2X
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
!

Loading…
Cancel
Save