@ -10,10 +10,13 @@ module psbn_d_cxx_mat_mod
contains
procedure , pass ( a ) :: get_nzeros = > d_cxx_get_nzeros
procedure , pass ( a ) :: get_fmt = > d_cxx_get_fmt
procedure , pass ( a ) :: get_diag = > d_cxx_get_diag
procedure , pass ( a ) :: d_base_csmm = > d_cxx_csmm
procedure , pass ( a ) :: d_base_csmv = > d_cxx_csmv
procedure , pass ( a ) :: d_base_cssm = > d_cxx_cssm
procedure , pass ( a ) :: d_base_cssv = > d_cxx_cssv
procedure , pass ( a ) :: d_scals = > d_cxx_scals
procedure , pass ( a ) :: d_scal = > d_cxx_scal
procedure , pass ( a ) :: csnmi = > d_cxx_csnmi
procedure , pass ( a ) :: reallocate_nz = > d_cxx_reallocate_nz
procedure , pass ( a ) :: csput = > d_cxx_csput
@ -26,16 +29,20 @@ module psbn_d_cxx_mat_mod
procedure , pass ( a ) :: mv_from_coo = > d_mv_cxx_from_coo
procedure , pass ( a ) :: mv_to_fmt = > d_mv_cxx_to_fmt
procedure , pass ( a ) :: mv_from_fmt = > d_mv_cxx_from_fmt
procedure , pass ( a ) :: d_csgetrow = > d_cxx_csgetrow
procedure , pass ( a ) :: get_size = > d_cxx_get_size
procedure , pass ( a ) :: free = > d_cxx_free
procedure , pass ( a ) :: trim = > d_cxx_trim
procedure , pass ( a ) :: print = > d_cxx_print
end type psbn_d_cxx_sparse_mat
private :: d_cxx_get_nzeros , d_cxx_csmm , d_cxx_csmv , d_cxx_cssm , d_cxx_cssv , &
& d_cxx_csput , d_cxx_reallocate_nz , d_cxx_allocate_mnnz , &
& d_cxx_free , d_cxx_print , d_cxx_get_fmt , d_cxx_csnmi , &
& d_cxx_free , d_cxx_print , d_cxx_get_fmt , d_cxx_csnmi , get_diag , &
& d_cp_cxx_to_coo , d_cp_cxx_from_coo , &
& d_mv_cxx_to_coo , d_mv_cxx_from_coo , &
& d_cp_cxx_to_fmt , d_cp_cxx_from_fmt , &
& d_mv_cxx_to_fmt , d_mv_cxx_from_fmt
& d_mv_cxx_to_fmt , d_mv_cxx_from_fmt , &
& d_cxx_scals , d_cxx_scal , d_cxx_trim , d_cxx_csgetrow , d_cxx_get_size
interface
@ -140,6 +147,26 @@ module psbn_d_cxx_mat_mod
end subroutine d_cxx_csput_impl
end interface
interface
subroutine d_cxx_csgetrow_impl ( imin , imax , a , nz , ia , ja , val , info , &
& jmin , jmax , iren , append , nzin , rscale , cscale )
use psb_const_mod
import psbn_d_cxx_sparse_mat
implicit none
class ( psbn_d_cxx_sparse_mat ) , intent ( in ) :: a
integer , intent ( in ) :: imin , imax
integer , intent ( out ) :: nz
integer , allocatable , intent ( inout ) :: ia ( : ) , ja ( : )
real ( psb_dpk_ ) , allocatable , intent ( inout ) :: val ( : )
integer , intent ( out ) :: info
logical , intent ( in ) , optional :: append
integer , intent ( in ) , optional :: iren ( : )
integer , intent ( in ) , optional :: jmin , jmax , nzin
logical , intent ( in ) , optional :: rscale , cscale
end subroutine d_cxx_csgetrow_impl
end interface
interface d_cxx_cssm_impl
subroutine d_cxx_cssv_impl ( alpha , a , x , beta , y , info , trans )
use psb_const_mod
@ -195,7 +222,7 @@ module psbn_d_cxx_mat_mod
contains
! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! !
! == == == == == == == == == == == == == == == == == == =
!
!
!
@ -205,7 +232,7 @@ contains
!
!
!
! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! !
! == == == == == == == == == == == == == == == == == == =
function d_cxx_get_fmt ( a ) result ( res )
implicit none
@ -221,8 +248,31 @@ contains
res = a % irp ( a % m + 1 ) - 1
end function d_cxx_get_nzeros
function d_cxx_get_size ( a ) result ( res )
implicit none
class ( psbn_d_cxx_sparse_mat ) , intent ( in ) :: a
integer :: res
res = - 1
! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! !
if ( allocated ( a % ja ) ) then
if ( res > = 0 ) then
res = min ( res , size ( a % ja ) )
else
res = size ( a % ja )
end if
end if
if ( allocated ( a % val ) ) then
if ( res > = 0 ) then
res = min ( res , size ( a % val ) )
else
res = size ( a % val )
end if
end if
end function d_cxx_get_size
! == == == == == == == == == == == == == == == == == == =
!
!
!
@ -232,7 +282,7 @@ contains
!
!
!
! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! !
! == == == == == == == == == == == == == == == == == == =
subroutine d_cxx_reallocate_nz ( nz , a )
@ -269,7 +319,7 @@ contains
end subroutine d_cxx_reallocate_nz
subroutine d_cxx_csput ( nz , val, ia, ja , a , imin , imax , jmin , jmax , info , gtl )
subroutine d_cxx_csput ( nz , ia, ja , val , a , imin , imax , jmin , jmax , info , gtl )
use psb_const_mod
use psb_error_mod
implicit none
@ -316,7 +366,7 @@ contains
if ( nz == 0 ) return
call d_cxx_csput_impl ( nz , val, ia, ja , a , imin , imax , jmin , jmax , info , gtl )
call d_cxx_csput_impl ( nz , ia, ja , val , a , imin , imax , jmin , jmax , info , gtl )
if ( info / = 0 ) go to 9999
call psb_erractionrestore ( err_act )
@ -332,6 +382,198 @@ contains
return
end subroutine d_cxx_csput
subroutine d_cxx_csgetrow ( imin , imax , a , nz , ia , ja , val , info , &
& jmin , jmax , iren , append , nzin , rscale , cscale )
! Output is always in COO format
use psb_error_mod
use psb_const_mod
implicit none
class ( psbn_d_cxx_sparse_mat ) , intent ( in ) :: a
integer , intent ( in ) :: imin , imax
integer , intent ( out ) :: nz
integer , allocatable , intent ( inout ) :: ia ( : ) , ja ( : )
real ( psb_dpk_ ) , allocatable , intent ( inout ) :: val ( : )
integer , intent ( out ) :: info
logical , intent ( in ) , optional :: append
integer , intent ( in ) , optional :: iren ( : )
integer , intent ( in ) , optional :: jmin , jmax , nzin
logical , intent ( in ) , optional :: rscale , cscale
Integer :: err_act
character ( len = 20 ) :: name = 'csget'
logical , parameter :: debug = . false .
call psb_erractionsave ( err_act )
info = 0
call d_cxx_csgetrow_impl ( imin , imax , a , nz , ia , ja , val , info , &
& jmin , jmax , iren , append , nzin , rscale , cscale )
if ( info / = 0 ) go to 9999
call psb_erractionrestore ( err_act )
return
9999 continue
call psb_erractionrestore ( err_act )
if ( err_act == psb_act_abort_ ) then
call psb_error ( )
return
end if
return
end subroutine d_cxx_csgetrow
subroutine d_cxx_csgetblk ( imin , imax , a , b , info , &
& jmin , jmax , iren , append , rscale , cscale )
! Output is always in COO format
use psb_error_mod
use psb_const_mod
implicit none
class ( psbn_d_cxx_sparse_mat ) , intent ( in ) :: a
class ( psbn_d_coo_sparse_mat ) , intent ( inout ) :: b
integer , intent ( in ) :: imin , imax
integer , intent ( out ) :: info
logical , intent ( in ) , optional :: append
integer , intent ( in ) , optional :: iren ( : )
integer , intent ( in ) , optional :: jmin , jmax
logical , intent ( in ) , optional :: rscale , cscale
Integer :: err_act , nzin , nzout
character ( len = 20 ) :: name = 'csget'
logical :: append_
logical , parameter :: debug = . false .
call psb_erractionsave ( err_act )
info = 0
if ( present ( append ) ) then
append_ = append
else
append_ = . false .
endif
if ( append_ ) then
nzin = a % get_nzeros ( )
else
nzin = 0
endif
call a % csget ( imin , imax , nzout , b % ia , b % ja , b % val , info , &
& jmin = jmin , jmax = jmax , iren = iren , append = append_ , &
& nzin = nzin , rscale = rscale , cscale = cscale )
if ( info / = 0 ) go to 9999
call b % set_nzeros ( nzin + nzout )
call b % fix ( info )
if ( info / = 0 ) go to 9999
call psb_erractionrestore ( err_act )
return
9999 continue
call psb_erractionrestore ( err_act )
if ( err_act == psb_act_abort_ ) then
call psb_error ( )
return
end if
return
end subroutine d_cxx_csgetblk
subroutine d_cxx_csclip ( a , b , info , &
& imin , imax , jmin , jmax , rscale , cscale )
! Output is always in COO format
use psb_error_mod
use psb_const_mod
implicit none
class ( psbn_d_cxx_sparse_mat ) , intent ( in ) :: a
class ( psbn_d_coo_sparse_mat ) , intent ( out ) :: b
integer , intent ( out ) :: info
integer , intent ( in ) , optional :: imin , imax , jmin , jmax
logical , intent ( in ) , optional :: rscale , cscale
Integer :: err_act , nzin , nzout , imin_ , imax_ , jmin_ , jmax_ , mb , nb
character ( len = 20 ) :: name = 'csget'
logical :: rscale_ , cscale_
logical , parameter :: debug = . false .
call psb_erractionsave ( err_act )
info = 0
nzin = 0
if ( present ( imin ) ) then
imin_ = imin
else
imin_ = 1
end if
if ( present ( imax ) ) then
imax_ = imax
else
imax_ = a % get_nrows ( )
end if
if ( present ( jmin ) ) then
jmin_ = jmin
else
jmin_ = 1
end if
if ( present ( jmax ) ) then
jmax_ = jmax
else
jmax_ = a % get_ncols ( )
end if
if ( present ( rscale ) ) then
rscale_ = rscale
else
rscale_ = . true .
end if
if ( present ( cscale ) ) then
cscale_ = cscale
else
cscale_ = . true .
end if
if ( rscale_ ) then
mb = imax_ - imin_ + 1
else
mb = a % get_nrows ( ) ! Should this be imax_ ? ?
endif
if ( cscale_ ) then
nb = jmax_ - jmin_ + 1
else
nb = a % get_ncols ( ) ! Should this be jmax_ ? ?
endif
call b % allocate ( mb , nb )
call a % csget ( imin_ , imax_ , nzout , b % ia , b % ja , b % val , info , &
& jmin = jmin_ , jmax = jmax_ , append = . false . , &
& nzin = nzin , rscale = rscale_ , cscale = cscale_ )
if ( info / = 0 ) go to 9999
call b % set_nzeros ( nzin + nzout )
call b % fix ( info )
if ( info / = 0 ) go to 9999
call psb_erractionrestore ( err_act )
return
9999 continue
call psb_erractionrestore ( err_act )
if ( err_act == psb_act_abort_ ) then
call psb_error ( )
return
end if
return
end subroutine d_cxx_csclip
subroutine d_cxx_free ( a )
implicit none
@ -349,6 +591,38 @@ contains
end subroutine d_cxx_free
subroutine d_cxx_trim ( a )
use psb_realloc_mod
use psb_error_mod
implicit none
class ( psbn_d_cxx_sparse_mat ) , intent ( inout ) :: a
Integer :: err_act , info , nz , m
character ( len = 20 ) :: name = 'trim'
logical , parameter :: debug = . false .
call psb_erractionsave ( err_act )
info = 0
m = a % get_nrows ( )
nz = a % get_nzeros ( )
if ( info == 0 ) call psb_realloc ( m + 1 , a % irp , info )
if ( info == 0 ) call psb_realloc ( nz , a % ja , info )
if ( info == 0 ) call psb_realloc ( nz , a % val , info )
if ( info / = 0 ) go to 9999
call psb_erractionrestore ( err_act )
return
9999 continue
call psb_erractionrestore ( err_act )
if ( err_act == psb_act_abort_ ) then
call psb_error ( )
return
end if
return
end subroutine d_cxx_trim
subroutine d_cp_cxx_to_coo ( a , b , info )
use psb_error_mod
@ -671,7 +945,6 @@ contains
subroutine d_cxx_print ( iout , a , iv , eirs , eics , head , ivr , ivc )
use psb_spmat_type
use psb_string_mod
implicit none
@ -752,7 +1025,7 @@ contains
end subroutine d_cxx_print
! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! !
! == == == == == == == == == == == == == == == == == == =
!
!
!
@ -763,7 +1036,7 @@ contains
!
!
!
! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! ! !
! == == == == == == == == == == == == == == == == == == =
subroutine d_cxx_csmv ( alpha , a , x , beta , y , info , trans )
@ -972,6 +1245,129 @@ contains
end function d_cxx_csnmi
subroutine d_cxx_get_diag ( a , d , info )
use psb_error_mod
use psb_const_mod
implicit none
class ( psbn_d_cxx_sparse_mat ) , intent ( in ) :: a
real ( psb_dpk_ ) , intent ( out ) :: d ( : )
integer , intent ( out ) :: info
Integer :: err_act , mnm , i , j , k
character ( len = 20 ) :: name = 'get_diag'
logical , parameter :: debug = . false .
info = 0
call psb_erractionsave ( err_act )
mnm = min ( a % get_nrows ( ) , a % get_ncols ( ) )
if ( size ( d ) < mnm ) then
info = 35
call psb_errpush ( info , name , i_err = ( / 2 , size ( d ) , 0 , 0 , 0 / ) )
go to 9999
end if
do i = 1 , mnm
do k = a % irp ( i ) , a % irp ( i + 1 ) - 1
j = a % ja ( k )
if ( ( j == i ) . and . ( j < = mnm ) ) then
d ( i ) = a % val ( k )
endif
enddo
end do
do i = mnm + 1 , size ( d )
d ( i ) = dzero
end do
call psb_erractionrestore ( err_act )
return
9999 continue
call psb_erractionrestore ( err_act )
if ( err_act == psb_act_abort_ ) then
call psb_error ( )
return
end if
return
end subroutine d_cxx_get_diag
subroutine d_cxx_scal ( d , a , info )
use psb_error_mod
use psb_const_mod
implicit none
class ( psbn_d_cxx_sparse_mat ) , intent ( inout ) :: a
real ( psb_dpk_ ) , intent ( in ) :: d ( : )
integer , intent ( out ) :: info
Integer :: err_act , mnm , i , j , m
character ( len = 20 ) :: name = 'scal'
logical , parameter :: debug = . false .
info = 0
call psb_erractionsave ( err_act )
m = a % get_nrows ( )
if ( size ( d ) < m ) then
info = 35
call psb_errpush ( info , name , i_err = ( / 2 , size ( d ) , 0 , 0 , 0 / ) )
go to 9999
end if
do i = 1 , m
do j = a % irp ( i ) , a % irp ( i + 1 ) - 1
a % val ( j ) = a % val ( j ) * d ( i )
end do
enddo
call psb_erractionrestore ( err_act )
return
9999 continue
call psb_erractionrestore ( err_act )
if ( err_act == psb_act_abort_ ) then
call psb_error ( )
return
end if
return
end subroutine d_cxx_scal
subroutine d_cxx_scals ( d , a , info )
use psb_error_mod
use psb_const_mod
implicit none
class ( psbn_d_cxx_sparse_mat ) , intent ( inout ) :: a
real ( psb_dpk_ ) , intent ( in ) :: d
integer , intent ( out ) :: info
Integer :: err_act , mnm , i , j , m
character ( len = 20 ) :: name = 'scal'
logical , parameter :: debug = . false .
info = 0
call psb_erractionsave ( err_act )
do i = 1 , a % get_nzeros ( )
a % val ( i ) = a % val ( i ) * d
enddo
call psb_erractionrestore ( err_act )
return
9999 continue
call psb_erractionrestore ( err_act )
if ( err_act == psb_act_abort_ ) then
call psb_error ( )
return
end if
return
end subroutine d_cxx_scals
end module psbn_d_cxx_mat_mod