Fixed interface to PSB_HALO.

Fixed in CDASB: deallocate avltree upon entering assembled state.
psblas3-type-indexed
Salvatore Filippone 18 years ago
parent 2ed0094102
commit 45b21b501a

@ -2,6 +2,11 @@ Changelog. A lot less detailed than usual, at least for past
history.
2007/01/23: Defined new field ext_index in desc_type, and
fixed long standing inconsistency in usage of overlap for
AS preconditioners. Modified halo to accept selector for
halo_index vs. ext_index.
2007/01/11: Migrated repository to SVN.
2007/01/11: MLD2P4 has been moved to the new org. Now tackling the

@ -46,12 +46,12 @@
! tran - character(optional). ???.
! mode - integer(optional).
!
subroutine psb_ihalom(x,desc_a,info,alpha,jx,ik,work,tran,mode)
subroutine psb_ihalom(x,desc_a,info,alpha,jx,ik,work,tran,mode,data)
use psb_descriptor_type
use psb_const_mod
use psi_mod
use psb_realloc_mod
use psb_check_mod
use psb_realloc_mod
use psb_error_mod
use psb_penv_mod
implicit none
@ -61,13 +61,13 @@ subroutine psb_ihalom(x,desc_a,info,alpha,jx,ik,work,tran,mode)
integer, intent(out) :: info
real(kind(1.d0)), intent(in), optional :: alpha
integer, intent(inout), optional, target :: work(:)
integer, intent(in), optional :: mode,jx,ik
integer, intent(in), optional :: mode,jx,ik,data
character, intent(in), optional :: tran
! locals
integer :: ictxt, np, me, &
& err_act, m, n, iix, jjx, ix, ijx, nrow, k, maxk, liwork,&
& imode, err
& imode, err,data_
integer, pointer :: xp(:,:), iwork(:)
character :: ltran
character(len=20) :: name, ch_err
@ -116,6 +116,14 @@ subroutine psb_ihalom(x,desc_a,info,alpha,jx,ik,work,tran,mode)
else
ltran = 'N'
endif
if (present(data)) then
data_ = data
else
data_ = psb_comm_halo_
endif
if (present(mode)) then
imode = mode
else
@ -179,7 +187,7 @@ subroutine psb_ihalom(x,desc_a,info,alpha,jx,ik,work,tran,mode)
! exchange halo elements
if(ltran.eq.'N') then
call psi_swapdata(imode,k,0,xp,&
& desc_a,iwork,info)
& desc_a,iwork,info,data=data_)
else if((ltran.eq.'T').or.(ltran.eq.'H')) then
call psi_swaptran(imode,k,1,xp,&
& desc_a,iwork,info)
@ -253,12 +261,12 @@ end subroutine psb_ihalom
! tran - character(optional). ???.
! mode - integer(optional).
!
subroutine psb_ihalov(x,desc_a,info,alpha,work,tran,mode)
subroutine psb_ihalov(x,desc_a,info,alpha,work,tran,mode,data)
use psb_descriptor_type
use psb_const_mod
use psi_mod
use psb_realloc_mod
use psb_check_mod
use psb_realloc_mod
use psb_error_mod
use psb_penv_mod
implicit none
@ -268,13 +276,13 @@ subroutine psb_ihalov(x,desc_a,info,alpha,work,tran,mode)
integer, intent(out) :: info
real(kind(1.d0)), intent(in), optional :: alpha
integer, intent(inout), optional, target :: work(:)
integer, intent(in), optional :: mode
integer, intent(in), optional :: mode,data
character, intent(in), optional :: tran
! locals
integer :: ictxt, np, me,&
& err_act, m, n, iix, jjx, ix, ijx, nrow, imode,&
& err, liwork
& err, liwork, data_
integer,pointer :: iwork(:)
character :: ltran
character(len=20) :: name, ch_err
@ -309,6 +317,11 @@ subroutine psb_ihalov(x,desc_a,info,alpha,work,tran,mode)
else
ltran = 'N'
endif
if (present(data)) then
data_ = data
else
data_ = psb_comm_halo_
endif
if (present(mode)) then
imode = mode
else
@ -367,7 +380,7 @@ subroutine psb_ihalov(x,desc_a,info,alpha,work,tran,mode)
! exchange halo elements
if(ltran.eq.'N') then
call psi_swapdata(imode,0,x(iix:size(x)),&
& desc_a,iwork,info)
& desc_a,iwork,info,data=data_)
else if((ltran.eq.'T').or.(ltran.eq.'H')) then
call psi_swaptran(imode,1,x(iix:size(x)),&
& desc_a,iwork,info)

@ -45,7 +45,7 @@
! tran - character(optional). ???.
! mode - integer(optional).
!
subroutine psb_zhalom(x,desc_a,info,alpha,jx,ik,work,tran,mode)
subroutine psb_zhalom(x,desc_a,info,alpha,jx,ik,work,tran,mode,data)
use psb_descriptor_type
use psb_const_mod
use psi_mod
@ -60,13 +60,13 @@ subroutine psb_zhalom(x,desc_a,info,alpha,jx,ik,work,tran,mode)
integer, intent(out) :: info
complex(kind(1.d0)), intent(in), optional :: alpha
complex(kind(1.d0)), optional, target :: work(:)
integer, intent(in), optional :: mode,jx,ik
integer, intent(in), optional :: mode,jx,ik,data
character, intent(in), optional :: tran
! locals
integer :: ictxt, np, me, &
& err_act, m, n, iix, jjx, ix, ijx, k, maxk, nrow, imode, i,&
& err, liwork
& err, liwork,data_
complex(kind(1.d0)),pointer :: iwork(:), xp(:,:)
character :: ltran
character(len=20) :: name, ch_err
@ -121,6 +121,12 @@ subroutine psb_zhalom(x,desc_a,info,alpha,jx,ik,work,tran,mode)
imode = IOR(psb_swap_send_,psb_swap_recv_)
endif
if (present(data)) then
data_ = data
else
data_ = psb_comm_halo_
endif
! check vector correctness
call psb_chkvect(m,1,size(x,1),ix,ijx,desc_a,info,iix,jjx)
if(info.ne.0) then
@ -177,7 +183,7 @@ subroutine psb_zhalom(x,desc_a,info,alpha,jx,ik,work,tran,mode)
xp => x(iix:size(x,1),jjx:jjx+k-1)
if(ltran.eq.'N') then
call psi_swapdata(imode,k,zzero,xp,&
& desc_a,iwork,info,data=psb_comm_halo_)
& desc_a,iwork,info,data=data_)
else if((ltran.eq.'T').or.(ltran.eq.'H')) then
call psi_swaptran(imode,k,zone,xp,&
&desc_a,iwork,info)
@ -252,7 +258,7 @@ end subroutine psb_zhalom
! tran - character(optional). ???.
! mode - integer(optional).
!
subroutine psb_zhalov(x,desc_a,info,alpha,work,tran,mode)
subroutine psb_zhalov(x,desc_a,info,alpha,work,tran,mode,data)
use psb_descriptor_type
use psb_const_mod
use psi_mod
@ -267,12 +273,12 @@ subroutine psb_zhalov(x,desc_a,info,alpha,work,tran,mode)
integer, intent(out) :: info
complex(kind(1.d0)), intent(in), optional :: alpha
complex(kind(1.d0)), target, optional :: work(:)
integer, intent(in), optional :: mode
integer, intent(in), optional :: mode,data
character, intent(in), optional :: tran
! locals
integer :: ictxt, np, me, err_act, &
& m, n, iix, jjx, ix, ijx, nrow, imode, err, liwork
& m, n, iix, jjx, ix, ijx, nrow, imode, err, liwork,data_
complex(kind(1.d0)),pointer :: iwork(:)
character :: ltran
character(len=20) :: name, ch_err
@ -311,6 +317,12 @@ subroutine psb_zhalov(x,desc_a,info,alpha,work,tran,mode)
imode = IOR(psb_swap_send_,psb_swap_recv_)
endif
if (present(data)) then
data_ = data
else
data_ = psb_comm_halo_
endif
! check vector correctness
call psb_chkvect(m,1,size(x,1),ix,ijx,desc_a,info,iix,jjx)
if(info.ne.0) then
@ -363,7 +375,7 @@ subroutine psb_zhalov(x,desc_a,info,alpha,work,tran,mode)
! exchange halo elements
if(ltran.eq.'N') then
call psi_swapdata(imode,zzero,x(iix:size(x)),&
& desc_a,iwork,info,data=psb_comm_halo_)
& desc_a,iwork,info,data=data_)
else if((ltran.eq.'T').or.(ltran.eq.'H')) then
call psi_swaptran(imode,zone,x(iix:size(x)),&
& desc_a,iwork,info)

@ -86,44 +86,44 @@ module psb_comm_mod
integer, intent(in), optional :: mode,data
character, intent(in), optional :: tran
end subroutine psb_dhalov
subroutine psb_ihalom(x,desc_a,info,alpha,jx,ik,work,tran,mode)
subroutine psb_ihalom(x,desc_a,info,alpha,jx,ik,work,tran,mode,data)
use psb_descriptor_type
integer, intent(inout) :: x(:,:)
type(psb_desc_type), intent(in) :: desc_a
integer, intent(out) :: info
real(kind(1.d0)), intent(in), optional :: alpha
integer, intent(inout), optional :: work(:)
integer, intent(in), optional :: mode,jx,ik
integer, intent(in), optional :: mode,jx,ik,data
character, intent(in), optional :: tran
end subroutine psb_ihalom
subroutine psb_ihalov(x,desc_a,info,alpha,work,tran,mode)
subroutine psb_ihalov(x,desc_a,info,alpha,work,tran,mode,data)
use psb_descriptor_type
integer, intent(inout) :: x(:)
type(psb_desc_type), intent(in) :: desc_a
integer, intent(out) :: info
real(kind(1.d0)), intent(in), optional :: alpha
integer, intent(inout), optional :: work(:)
integer, intent(in), optional :: mode
integer, intent(in), optional :: mode,data
character, intent(in), optional :: tran
end subroutine psb_ihalov
subroutine psb_zhalom(x,desc_a,info,alpha,jx,ik,work,tran,mode)
subroutine psb_zhalom(x,desc_a,info,alpha,jx,ik,work,tran,mode,data)
use psb_descriptor_type
complex(kind(1.d0)), intent(inout) :: x(:,:)
type(psb_desc_type), intent(in) :: desc_a
integer, intent(out) :: info
complex(kind(1.d0)), intent(in), optional :: alpha
complex(kind(1.d0)), target, optional :: work(:)
integer, intent(in), optional :: mode,jx,ik
integer, intent(in), optional :: mode,jx,ik,data
character, intent(in), optional :: tran
end subroutine psb_zhalom
subroutine psb_zhalov(x,desc_a,info,alpha,work,tran,mode)
subroutine psb_zhalov(x,desc_a,info,alpha,work,tran,mode,data)
use psb_descriptor_type
complex(kind(1.d0)), intent(inout) :: x(:)
type(psb_desc_type), intent(in) :: desc_a
integer, intent(out) :: info
complex(kind(1.d0)), intent(in), optional :: alpha
complex(kind(1.d0)), target, optional :: work(:)
integer, intent(in), optional :: mode
integer, intent(in), optional :: mode,data
character, intent(in), optional :: tran
end subroutine psb_zhalov
end interface

@ -135,6 +135,17 @@ subroutine psb_icdasb(desc_a,info,ext_hv)
call psb_errpush(info,name)
goto 9999
end if
! Finally, cleanup the AVL tree, as it is really only needed
! when building.
if (allocated(desc_a%ptree)) then
call FreePairSearchTree(desc_a%ptree)
deallocate(desc_a%ptree,stat=info)
if (info /= 0) then
info=2059
call psb_errpush(info,name)
goto 9999
end if
end if
! Ok, register into MATRIX_DATA & free temporary work areas
desc_a%matrix_data(psb_dec_type_) = psb_desc_asb_
else

Loading…
Cancel
Save