*** empty log message ***

psblas3-type-indexed
Alfredo Buttari 19 years ago
parent 4732e49635
commit 31e309760f

@ -51,15 +51,15 @@ end subroutine FCpsb_perror
subroutine FCpsb_get_errstatus(s)
function FCpsb_get_errstatus()
use psb_error_mod
implicit none
integer, intent(out) :: s
integer :: FCpsb_get_errstatus
call psb_get_errstatus(s)
FCpsb_get_errstatus = psb_get_errstatus()
end subroutine FCpsb_get_errstatus
end function FCpsb_get_errstatus

@ -50,7 +50,8 @@ contains
integer :: err_act, int_err(5)
character(len=20) :: name, ch_err
info=0
if(psb_get_errstatus().ne.0) return
info=0
name='psb_chkvect'
call psb_erractionsave(err_act)
@ -173,7 +174,8 @@ contains
integer :: err_act, int_err(5)
character(len=20) :: name, ch_err
info=0
if(psb_get_errstatus().ne.0) return
info=0
name='psb_chkglobvect'
call psb_erractionsave(err_act)
@ -295,7 +297,8 @@ contains
integer :: err_act, int_err(5)
character(len=20) :: name, ch_err
info=0
if(psb_get_errstatus().ne.0) return
info=0
name='psb_chkmat'
call psb_erractionsave(err_act)

@ -102,10 +102,10 @@ contains
! checks the status of the error condition
subroutine psb_get_errstatus(s)
integer, intent(out) :: s
s=error_status
end subroutine psb_get_errstatus
function psb_get_errstatus()
integer :: psb_get_errstatus
psb_get_errstatus=error_status
end function psb_get_errstatus

@ -74,6 +74,9 @@ module psb_psblas_mod
type(psb_desc_type), intent (in) :: desc_a
integer, intent(out) :: info
end function psb_damaxv
end interface
interface psb_amaxs
subroutine psb_damaxvs(res,x,desc_a,info)
use psb_descriptor_type
real(kind(1.d0)), intent (out) :: res
@ -143,6 +146,9 @@ module psb_psblas_mod
type(psb_desc_type), intent (in) :: desc_a
integer, intent(out) :: info
end function psb_dnrm2v
end interface
interface psb_nrm2s
subroutine psb_dnrm2vs(res,x,desc_a,info)
use psb_descriptor_type
real(kind(1.d0)), intent (out) :: res
@ -230,21 +236,21 @@ module psb_psblas_mod
end interface
interface psb_gelp
subroutine psb_dgelp(trans,iperm,x,desc_a,info)
use psb_descriptor_type
type(psb_desc_type), intent(in) :: desc_a
real(kind(1.d0)), intent(inout) :: x(:,:)
integer, intent(inout) :: iperm(:),info
character, intent(in) :: trans
end subroutine psb_dgelp
subroutine psb_dgelpv(trans,iperm,x,desc_a,info)
use psb_descriptor_type
type(psb_desc_type), intent(in) :: desc_a
real(kind(1.d0)), intent(inout) :: x(:)
integer, intent(inout) :: iperm(:),info
character, intent(in) :: trans
end subroutine psb_dgelpv
end interface
! interface psb_gelp
! subroutine psb_dgelp(trans,iperm,x,desc_a,info)
! use psb_descriptor_type
! type(psb_desc_type), intent(in) :: desc_a
! real(kind(1.d0)), intent(inout) :: x(:,:)
! integer, intent(inout) :: iperm(:),info
! character, intent(in) :: trans
! end subroutine psb_dgelp
! subroutine psb_dgelpv(trans,iperm,x,desc_a,info)
! use psb_descriptor_type
! type(psb_desc_type), intent(in) :: desc_a
! real(kind(1.d0)), intent(inout) :: x(:)
! integer, intent(inout) :: iperm(:),info
! character, intent(in) :: trans
! end subroutine psb_dgelpv
! end interface
end module psb_psblas_mod

@ -31,7 +31,8 @@ Contains
name='psb_dreallocate1i'
call psb_erractionsave(err_act)
info=0
if(psb_get_errstatus().ne.0) return
info=0
if (associated(rrax)) then
dim=size(rrax)
If (dim /= len) Then
@ -252,7 +253,8 @@ Contains
name='psb_dreallocate2i'
call psb_erractionsave(err_act)
info=0
if(psb_get_errstatus().ne.0) return
info=0
call psb_dreallocate1i(len,rrax,info,pad=pad)
if (info /= 0) then
err=4000
@ -346,7 +348,8 @@ Contains
name='psb_dreallocate1it'
call psb_erractionsave(err_act)
info=0
if(psb_get_errstatus().ne.0) return
info=0
if (associated(rrax)) then
dim=size(rrax)
If (dim /= len) Then

@ -42,9 +42,9 @@ module psb_spmat_type
module procedure psb_dspallocate, psb_dspall3, psb_dspallmk, psb_dspallmknz
end interface
interface psb_spfree
module procedure psb_dspfree
end interface
! interface psb_spfree
! module procedure psb_dspfree
! end interface
interface psb_spreinit
module procedure psb_dspreinit
@ -317,24 +317,24 @@ contains
End Subroutine psb_dspclone
subroutine psb_dspfree(a,info)
implicit none
!....Parameters...
Type(psb_dspmat_type), intent(inout) :: A
Integer, intent(out) :: info
! subroutine psb_dspfree(a,info)
! implicit none
! !....Parameters...
! Type(psb_dspmat_type), intent(inout) :: A
! Integer, intent(out) :: info
!locals
logical, parameter :: debug=.false.
! !locals
! logical, parameter :: debug=.false.
INFO = 0
! INFO = 0
deallocate(a%aspk,a%ia1,a%ia2,a%pr,a%pl,STAT=INFO)
! deallocate(a%aspk,a%ia1,a%ia2,a%pr,a%pl,STAT=INFO)
call psb_nullify_sp(a)
! call psb_nullify_sp(a)
Return
! Return
End Subroutine psb_dspfree
! End Subroutine psb_dspfree
end module psb_spmat_type

@ -391,11 +391,11 @@ Module psb_tools_mod
type(psb_dspmat_type), intent(inout) ::a
integer, intent(out) :: info
end subroutine psb_dspfree
!!$ subroutine psb_dspfrees(a,info)
!!$ use psb_spmat_type
!!$ type(psb_dspmat_type), intent(inout) ::a
!!$ integer, intent(out) :: info
!!$ end subroutine psb_dspfrees
subroutine psb_dspfrees(a,info)
use psb_spmat_type
type(psb_dspmat_type), intent(inout) ::a
integer, intent(out) :: info
end subroutine psb_dspfrees
end interface

Loading…
Cancel
Save