|
|
|
@ -36,7 +36,7 @@ module psb_c_bjacprec
|
|
|
|
|
type, extends(psb_c_base_prec_type) :: psb_c_bjac_prec_type
|
|
|
|
|
integer(psb_ipk_), allocatable :: iprcparm(:)
|
|
|
|
|
type(psb_cspmat_type), allocatable :: av(:)
|
|
|
|
|
type(psb_c_vect_type), allocatable :: dv
|
|
|
|
|
type(psb_c_vect_type), allocatable :: dv, wrk(:)
|
|
|
|
|
contains
|
|
|
|
|
procedure, pass(prec) :: c_apply_v => psb_c_bjac_apply_vect
|
|
|
|
|
procedure, pass(prec) :: c_apply => psb_c_bjac_apply
|
|
|
|
@ -49,6 +49,9 @@ module psb_c_bjacprec
|
|
|
|
|
procedure, pass(prec) :: free => psb_c_bjac_precfree
|
|
|
|
|
procedure, pass(prec) :: sizeof => psb_c_bjac_sizeof
|
|
|
|
|
procedure, pass(prec) :: get_nzeros => psb_c_bjac_get_nzeros
|
|
|
|
|
procedure, pass(prec) :: allocate_wrk => psb_c_bjac_allocate_wrk
|
|
|
|
|
procedure, pass(prec) :: free_wrk => psb_c_bjac_free_wrk
|
|
|
|
|
procedure, pass(prec) :: is_allocated_wrk => psb_c_bjac_is_allocated_wrk
|
|
|
|
|
end type psb_c_bjac_prec_type
|
|
|
|
|
|
|
|
|
|
private :: psb_c_bjac_sizeof, psb_c_bjac_precdescr, psb_c_bjac_get_nzeros
|
|
|
|
@ -308,4 +311,111 @@ contains
|
|
|
|
|
|
|
|
|
|
end subroutine psb_c_bjac_clone
|
|
|
|
|
|
|
|
|
|
subroutine psb_c_bjac_allocate_wrk(prec,info,vmold,desc)
|
|
|
|
|
use psb_base_mod
|
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
|
|
! Arguments
|
|
|
|
|
class(psb_c_bjac_prec_type), intent(inout) :: prec
|
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
|
class(psb_c_base_vect_type), intent(in), optional :: vmold
|
|
|
|
|
type(psb_desc_type), intent(in), optional :: desc
|
|
|
|
|
|
|
|
|
|
! Local variables
|
|
|
|
|
integer(psb_ipk_) :: err_act, i
|
|
|
|
|
character(len=20) :: name
|
|
|
|
|
|
|
|
|
|
info=psb_success_
|
|
|
|
|
name = 'psb_c_allocate_wrk'
|
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
|
|
|
|
|
|
if (psb_get_errstatus().ne.0) goto 9999
|
|
|
|
|
if (allocated(prec%wrk)) then
|
|
|
|
|
if (size(prec%wrk)<2) then
|
|
|
|
|
do i=1,size(prec%wrk)
|
|
|
|
|
if (info == 0) call prec%wrk(i)%free(info)
|
|
|
|
|
end do
|
|
|
|
|
if (info == 0) deallocate(prec%wrk,stat=info)
|
|
|
|
|
end if
|
|
|
|
|
end if
|
|
|
|
|
if (info /= 0) then
|
|
|
|
|
info = psb_err_internal_error_; call psb_errpush(info,name,a_err="deallocate"); goto 9999
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
if (.not.allocated(prec%wrk)) then
|
|
|
|
|
if (.not.present(desc)) then
|
|
|
|
|
info = psb_err_internal_error_; call psb_errpush(info,name,a_err="no desc?"); goto 9999
|
|
|
|
|
end if
|
|
|
|
|
allocate(prec%wrk(2),stat=info)
|
|
|
|
|
do i=1, 2
|
|
|
|
|
if (info == 0) call psb_geall(prec%wrk(i),desc,info)
|
|
|
|
|
if (info == 0) call psb_geasb(prec%wrk(i),desc,info,mold=vmold,scratch=.true.)
|
|
|
|
|
end do
|
|
|
|
|
end if
|
|
|
|
|
if (info /= 0) then
|
|
|
|
|
info = psb_err_internal_error_; call psb_errpush(info,name,a_err="allocate"); goto 9999
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
|
return
|
|
|
|
|
|
|
|
|
|
9999 call psb_error_handler(err_act)
|
|
|
|
|
return
|
|
|
|
|
|
|
|
|
|
end subroutine psb_c_bjac_allocate_wrk
|
|
|
|
|
|
|
|
|
|
subroutine psb_c_bjac_free_wrk(prec,info)
|
|
|
|
|
use psb_base_mod
|
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
|
|
! Arguments
|
|
|
|
|
class(psb_c_bjac_prec_type), intent(inout) :: prec
|
|
|
|
|
integer(psb_ipk_), intent(out) :: info
|
|
|
|
|
|
|
|
|
|
! Local variables
|
|
|
|
|
integer(psb_ipk_) :: err_act
|
|
|
|
|
integer(psb_ipk_) :: i
|
|
|
|
|
character(len=20) :: name
|
|
|
|
|
|
|
|
|
|
info=psb_success_
|
|
|
|
|
name = 'psb_c_allocate_wrk'
|
|
|
|
|
call psb_erractionsave(err_act)
|
|
|
|
|
|
|
|
|
|
if (psb_get_errstatus().ne.0) goto 9999
|
|
|
|
|
|
|
|
|
|
info = psb_success_
|
|
|
|
|
if (allocated(prec%wrk)) then
|
|
|
|
|
do i=1,size(prec%wrk)
|
|
|
|
|
if (info == 0) call prec%wrk(i)%free(info)
|
|
|
|
|
end do
|
|
|
|
|
if (info == 0) deallocate(prec%wrk,stat=info)
|
|
|
|
|
end if
|
|
|
|
|
if (info /= 0) then
|
|
|
|
|
info = psb_err_internal_error_; call psb_errpush(info,name,a_err="deallocate"); goto 9999
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
call psb_erractionrestore(err_act)
|
|
|
|
|
return
|
|
|
|
|
|
|
|
|
|
9999 call psb_error_handler(err_act)
|
|
|
|
|
return
|
|
|
|
|
|
|
|
|
|
end subroutine psb_c_bjac_free_wrk
|
|
|
|
|
|
|
|
|
|
function psb_c_bjac_is_allocated_wrk(prec) result(res)
|
|
|
|
|
use psb_base_mod
|
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
|
|
! Arguments
|
|
|
|
|
class(psb_c_bjac_prec_type), intent(in) :: prec
|
|
|
|
|
logical :: res
|
|
|
|
|
|
|
|
|
|
! In the base version we can say yes, because
|
|
|
|
|
! there is nothing to allocate
|
|
|
|
|
|
|
|
|
|
res = allocated(prec%wrk)
|
|
|
|
|
|
|
|
|
|
end function psb_c_bjac_is_allocated_wrk
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
end module psb_c_bjacprec
|
|
|
|
|