|
|
|
@ -1,3 +1,57 @@
|
|
|
|
|
!!$
|
|
|
|
|
!!$ Parallel Sparse BLAS version 3.0
|
|
|
|
|
!!$ (C) Copyright 2006, 2007, 2008, 2009, 2010
|
|
|
|
|
!!$ Salvatore Filippone University of Rome Tor Vergata
|
|
|
|
|
!!$ Alfredo Buttari CNRS-IRIT, Toulouse
|
|
|
|
|
!!$
|
|
|
|
|
!!$ Redistribution and use in source and binary forms, with or without
|
|
|
|
|
!!$ modification, are permitted provided that the following conditions
|
|
|
|
|
!!$ are met:
|
|
|
|
|
!!$ 1. Redistributions of source code must retain the above copyright
|
|
|
|
|
!!$ notice, this list of conditions and the following disclaimer.
|
|
|
|
|
!!$ 2. Redistributions in binary form must reproduce the above copyright
|
|
|
|
|
!!$ notice, this list of conditions, and the following disclaimer in the
|
|
|
|
|
!!$ documentation and/or other materials provided with the distribution.
|
|
|
|
|
!!$ 3. The name of the PSBLAS group or the names of its contributors may
|
|
|
|
|
!!$ not be used to endorse or promote products derived from this
|
|
|
|
|
!!$ software without specific written permission.
|
|
|
|
|
!!$
|
|
|
|
|
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
|
|
|
|
|
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
|
|
|
|
|
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
|
|
|
|
|
!!$ PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
|
|
|
|
|
!!$ BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
|
|
|
|
|
!!$ CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
|
|
|
|
|
!!$ SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
|
|
|
|
|
!!$ INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
|
|
|
|
|
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
|
|
|
|
|
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
|
|
|
|
|
!!$ POSSIBILITY OF SUCH DAMAGE.
|
|
|
|
|
!!$
|
|
|
|
|
!!$
|
|
|
|
|
!
|
|
|
|
|
!
|
|
|
|
|
! package: psb_hash_map_mod
|
|
|
|
|
! Defines the HASH_MAP type.
|
|
|
|
|
!
|
|
|
|
|
! This is the index map of choice for large index spaces.
|
|
|
|
|
! If the global index space is very large (larger than the threshold value
|
|
|
|
|
! which may be set by the user), then it is not advisable to have a full
|
|
|
|
|
! GLOB_TO_LOC array; therefore we only record the global indices that do have a
|
|
|
|
|
! local counterpart, so that the local storage will be proportional to
|
|
|
|
|
! N_COL.
|
|
|
|
|
! The idea is that glb_lc(:,1) will hold sorted global indices, and
|
|
|
|
|
! glb_lc(:,2) the corresponding local indices, so that we may do a binary search.
|
|
|
|
|
! To cut down the search time we partition glb_lc into a set of lists
|
|
|
|
|
! addressed by hashv(:) based on the value of the lowest
|
|
|
|
|
! PSB_HASH_BITS bits of the global index.
|
|
|
|
|
! During the build phase glb_lc() will store the indices of the internal points,
|
|
|
|
|
! i.e. local indices 1:NROW, since those are known ad CDALL time.
|
|
|
|
|
! The halo indices that we encounter during the build phase are put in
|
|
|
|
|
! a PSB_HASH_TYPE data structure, which implements a very simple hash; this
|
|
|
|
|
! hash will nonetheless be quite fast at low occupancy rates.
|
|
|
|
|
! At assembly time, we move everything into hashv(:) and glb_lc(:,:).
|
|
|
|
|
!
|
|
|
|
|
module psb_hash_map_mod
|
|
|
|
|
use psb_const_mod
|
|
|
|
|
use psb_desc_const_mod
|
|
|
|
@ -10,7 +64,7 @@ module psb_hash_map_mod
|
|
|
|
|
integer, allocatable :: hashv(:), glb_lc(:,:), loc_to_glob(:)
|
|
|
|
|
type(psb_hash_type), allocatable :: hash
|
|
|
|
|
|
|
|
|
|
contains
|
|
|
|
|
contains
|
|
|
|
|
|
|
|
|
|
procedure, pass(idxmap) :: init_vl => hash_init_vl
|
|
|
|
|
procedure, pass(idxmap) :: hash_map_init => hash_init_vg
|
|
|
|
@ -39,9 +93,9 @@ module psb_hash_map_mod
|
|
|
|
|
|
|
|
|
|
procedure, pass(idxmap) :: bld_g2l_map => hash_bld_g2l_map
|
|
|
|
|
|
|
|
|
|
end type psb_hash_map
|
|
|
|
|
end type psb_hash_map
|
|
|
|
|
|
|
|
|
|
private :: hash_init_vl, hash_init_vg, hash_sizeof, hash_asb, &
|
|
|
|
|
private :: hash_init_vl, hash_init_vg, hash_sizeof, hash_asb, &
|
|
|
|
|
& hash_free, hash_get_fmt, hash_l2gs1, hash_l2gs2, &
|
|
|
|
|
& hash_l2gv1, hash_l2gv2, hash_g2ls1, hash_g2ls2, &
|
|
|
|
|
& hash_g2lv1, hash_g2lv2, hash_g2ls1_ins, hash_g2ls2_ins, &
|
|
|
|
@ -50,22 +104,22 @@ module psb_hash_map_mod
|
|
|
|
|
& hash_inner_cnv1, hash_inner_cnv2, hash_row_extendable
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
interface hash_inner_cnv
|
|
|
|
|
interface hash_inner_cnv
|
|
|
|
|
module procedure hash_inner_cnvs1, hash_inner_cnvs2,&
|
|
|
|
|
& hash_inner_cnv1, hash_inner_cnv2
|
|
|
|
|
end interface hash_inner_cnv
|
|
|
|
|
private :: hash_inner_cnv
|
|
|
|
|
end interface hash_inner_cnv
|
|
|
|
|
private :: hash_inner_cnv
|
|
|
|
|
|
|
|
|
|
contains
|
|
|
|
|
|
|
|
|
|
function hash_row_extendable(idxmap) result(val)
|
|
|
|
|
function hash_row_extendable(idxmap) result(val)
|
|
|
|
|
implicit none
|
|
|
|
|
class(psb_hash_map), intent(in) :: idxmap
|
|
|
|
|
logical :: val
|
|
|
|
|
val = .true.
|
|
|
|
|
end function hash_row_extendable
|
|
|
|
|
end function hash_row_extendable
|
|
|
|
|
|
|
|
|
|
function hash_sizeof(idxmap) result(val)
|
|
|
|
|
function hash_sizeof(idxmap) result(val)
|
|
|
|
|
implicit none
|
|
|
|
|
class(psb_hash_map), intent(in) :: idxmap
|
|
|
|
|
integer(psb_long_int_k_) :: val
|
|
|
|
@ -79,10 +133,10 @@ contains
|
|
|
|
|
if (allocated(idxmap%hash)) &
|
|
|
|
|
& val = val + psb_sizeof(idxmap%hash)
|
|
|
|
|
|
|
|
|
|
end function hash_sizeof
|
|
|
|
|
end function hash_sizeof
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine hash_free(idxmap)
|
|
|
|
|
subroutine hash_free(idxmap)
|
|
|
|
|
implicit none
|
|
|
|
|
class(psb_hash_map), intent(inout) :: idxmap
|
|
|
|
|
integer :: info
|
|
|
|
@ -99,10 +153,10 @@ contains
|
|
|
|
|
|
|
|
|
|
call idxmap%psb_indx_map%free()
|
|
|
|
|
|
|
|
|
|
end subroutine hash_free
|
|
|
|
|
end subroutine hash_free
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine hash_l2gs1(idx,idxmap,info,mask,owned)
|
|
|
|
|
subroutine hash_l2gs1(idx,idxmap,info,mask,owned)
|
|
|
|
|
implicit none
|
|
|
|
|
class(psb_hash_map), intent(in) :: idxmap
|
|
|
|
|
integer, intent(inout) :: idx
|
|
|
|
@ -119,9 +173,9 @@ contains
|
|
|
|
|
call idxmap%l2g(idxv,info,owned=owned)
|
|
|
|
|
idx = idxv(1)
|
|
|
|
|
|
|
|
|
|
end subroutine hash_l2gs1
|
|
|
|
|
end subroutine hash_l2gs1
|
|
|
|
|
|
|
|
|
|
subroutine hash_l2gs2(idxin,idxout,idxmap,info,mask,owned)
|
|
|
|
|
subroutine hash_l2gs2(idxin,idxout,idxmap,info,mask,owned)
|
|
|
|
|
implicit none
|
|
|
|
|
class(psb_hash_map), intent(in) :: idxmap
|
|
|
|
|
integer, intent(in) :: idxin
|
|
|
|
@ -133,10 +187,10 @@ contains
|
|
|
|
|
idxout = idxin
|
|
|
|
|
call idxmap%l2g(idxout,info,mask,owned)
|
|
|
|
|
|
|
|
|
|
end subroutine hash_l2gs2
|
|
|
|
|
end subroutine hash_l2gs2
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine hash_l2gv1(idx,idxmap,info,mask,owned)
|
|
|
|
|
subroutine hash_l2gv1(idx,idxmap,info,mask,owned)
|
|
|
|
|
implicit none
|
|
|
|
|
class(psb_hash_map), intent(in) :: idxmap
|
|
|
|
|
integer, intent(inout) :: idx(:)
|
|
|
|
@ -189,9 +243,9 @@ contains
|
|
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
end subroutine hash_l2gv1
|
|
|
|
|
end subroutine hash_l2gv1
|
|
|
|
|
|
|
|
|
|
subroutine hash_l2gv2(idxin,idxout,idxmap,info,mask,owned)
|
|
|
|
|
subroutine hash_l2gv2(idxin,idxout,idxmap,info,mask,owned)
|
|
|
|
|
implicit none
|
|
|
|
|
class(psb_hash_map), intent(in) :: idxmap
|
|
|
|
|
integer, intent(in) :: idxin(:)
|
|
|
|
@ -210,10 +264,10 @@ contains
|
|
|
|
|
info = -3
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
end subroutine hash_l2gv2
|
|
|
|
|
end subroutine hash_l2gv2
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine hash_g2ls1(idx,idxmap,info,mask,owned)
|
|
|
|
|
subroutine hash_g2ls1(idx,idxmap,info,mask,owned)
|
|
|
|
|
implicit none
|
|
|
|
|
class(psb_hash_map), intent(in) :: idxmap
|
|
|
|
|
integer, intent(inout) :: idx
|
|
|
|
@ -231,9 +285,9 @@ contains
|
|
|
|
|
call idxmap%g2l(idxv,info,owned=owned)
|
|
|
|
|
idx = idxv(1)
|
|
|
|
|
|
|
|
|
|
end subroutine hash_g2ls1
|
|
|
|
|
end subroutine hash_g2ls1
|
|
|
|
|
|
|
|
|
|
subroutine hash_g2ls2(idxin,idxout,idxmap,info,mask,owned)
|
|
|
|
|
subroutine hash_g2ls2(idxin,idxout,idxmap,info,mask,owned)
|
|
|
|
|
implicit none
|
|
|
|
|
class(psb_hash_map), intent(in) :: idxmap
|
|
|
|
|
integer, intent(in) :: idxin
|
|
|
|
@ -245,10 +299,10 @@ contains
|
|
|
|
|
idxout = idxin
|
|
|
|
|
call idxmap%g2l(idxout,info,mask,owned)
|
|
|
|
|
|
|
|
|
|
end subroutine hash_g2ls2
|
|
|
|
|
end subroutine hash_g2ls2
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine hash_g2lv1(idx,idxmap,info,mask,owned)
|
|
|
|
|
subroutine hash_g2lv1(idx,idxmap,info,mask,owned)
|
|
|
|
|
use psb_penv_mod
|
|
|
|
|
use psb_sort_mod
|
|
|
|
|
implicit none
|
|
|
|
@ -362,9 +416,9 @@ contains
|
|
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
end subroutine hash_g2lv1
|
|
|
|
|
end subroutine hash_g2lv1
|
|
|
|
|
|
|
|
|
|
subroutine hash_g2lv2(idxin,idxout,idxmap,info,mask,owned)
|
|
|
|
|
subroutine hash_g2lv2(idxin,idxout,idxmap,info,mask,owned)
|
|
|
|
|
implicit none
|
|
|
|
|
class(psb_hash_map), intent(in) :: idxmap
|
|
|
|
|
integer, intent(in) :: idxin(:)
|
|
|
|
@ -384,11 +438,11 @@ contains
|
|
|
|
|
info = -3
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
end subroutine hash_g2lv2
|
|
|
|
|
end subroutine hash_g2lv2
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine hash_g2ls1_ins(idx,idxmap,info,mask)
|
|
|
|
|
subroutine hash_g2ls1_ins(idx,idxmap,info,mask)
|
|
|
|
|
use psb_realloc_mod
|
|
|
|
|
use psb_sort_mod
|
|
|
|
|
implicit none
|
|
|
|
@ -407,9 +461,9 @@ contains
|
|
|
|
|
call idxmap%g2l_ins(idxv,info)
|
|
|
|
|
idx = idxv(1)
|
|
|
|
|
|
|
|
|
|
end subroutine hash_g2ls1_ins
|
|
|
|
|
end subroutine hash_g2ls1_ins
|
|
|
|
|
|
|
|
|
|
subroutine hash_g2ls2_ins(idxin,idxout,idxmap,info,mask)
|
|
|
|
|
subroutine hash_g2ls2_ins(idxin,idxout,idxmap,info,mask)
|
|
|
|
|
implicit none
|
|
|
|
|
class(psb_hash_map), intent(inout) :: idxmap
|
|
|
|
|
integer, intent(in) :: idxin
|
|
|
|
@ -420,10 +474,10 @@ contains
|
|
|
|
|
idxout = idxin
|
|
|
|
|
call idxmap%g2l_ins(idxout,info)
|
|
|
|
|
|
|
|
|
|
end subroutine hash_g2ls2_ins
|
|
|
|
|
end subroutine hash_g2ls2_ins
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine hash_g2lv1_ins(idx,idxmap,info,mask)
|
|
|
|
|
subroutine hash_g2lv1_ins(idx,idxmap,info,mask)
|
|
|
|
|
use psb_error_mod
|
|
|
|
|
use psb_realloc_mod
|
|
|
|
|
use psb_sort_mod
|
|
|
|
@ -559,9 +613,9 @@ contains
|
|
|
|
|
end if
|
|
|
|
|
return
|
|
|
|
|
|
|
|
|
|
end subroutine hash_g2lv1_ins
|
|
|
|
|
end subroutine hash_g2lv1_ins
|
|
|
|
|
|
|
|
|
|
subroutine hash_g2lv2_ins(idxin,idxout,idxmap,info,mask)
|
|
|
|
|
subroutine hash_g2lv2_ins(idxin,idxout,idxmap,info,mask)
|
|
|
|
|
implicit none
|
|
|
|
|
class(psb_hash_map), intent(inout) :: idxmap
|
|
|
|
|
integer, intent(in) :: idxin(:)
|
|
|
|
@ -579,9 +633,9 @@ contains
|
|
|
|
|
info = -3
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
end subroutine hash_g2lv2_ins
|
|
|
|
|
end subroutine hash_g2lv2_ins
|
|
|
|
|
|
|
|
|
|
subroutine hash_init_vl(idxmap,ictxt,vl,info)
|
|
|
|
|
subroutine hash_init_vl(idxmap,ictxt,vl,info)
|
|
|
|
|
use psb_penv_mod
|
|
|
|
|
use psb_error_mod
|
|
|
|
|
use psb_sort_mod
|
|
|
|
@ -645,9 +699,9 @@ contains
|
|
|
|
|
|
|
|
|
|
call hash_init_vlu(idxmap,ictxt,m,nlu,vlu,info)
|
|
|
|
|
|
|
|
|
|
end subroutine hash_init_vl
|
|
|
|
|
end subroutine hash_init_vl
|
|
|
|
|
|
|
|
|
|
subroutine hash_init_vg(idxmap,ictxt,vg,info)
|
|
|
|
|
subroutine hash_init_vg(idxmap,ictxt,vg,info)
|
|
|
|
|
use psb_penv_mod
|
|
|
|
|
use psb_error_mod
|
|
|
|
|
implicit none
|
|
|
|
@ -698,10 +752,10 @@ contains
|
|
|
|
|
call hash_init_vlu(idxmap,ictxt,n,nl,vlu,info)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
end subroutine hash_init_vg
|
|
|
|
|
end subroutine hash_init_vg
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine hash_init_vlu(idxmap,ictxt,ntot,nl,vlu,info)
|
|
|
|
|
subroutine hash_init_vlu(idxmap,ictxt,ntot,nl,vlu,info)
|
|
|
|
|
use psb_penv_mod
|
|
|
|
|
use psb_error_mod
|
|
|
|
|
use psb_sort_mod
|
|
|
|
@ -752,11 +806,11 @@ contains
|
|
|
|
|
call hash_bld_g2l_map(idxmap,info)
|
|
|
|
|
call idxmap%set_state(psb_desc_bld_)
|
|
|
|
|
|
|
|
|
|
end subroutine hash_init_vlu
|
|
|
|
|
end subroutine hash_init_vlu
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine hash_bld_g2l_map(idxmap,info)
|
|
|
|
|
subroutine hash_bld_g2l_map(idxmap,info)
|
|
|
|
|
use psb_penv_mod
|
|
|
|
|
use psb_error_mod
|
|
|
|
|
use psb_sort_mod
|
|
|
|
@ -855,10 +909,10 @@ contains
|
|
|
|
|
end if
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
|
|
end subroutine hash_bld_g2l_map
|
|
|
|
|
end subroutine hash_bld_g2l_map
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine hash_asb(idxmap,info)
|
|
|
|
|
subroutine hash_asb(idxmap,info)
|
|
|
|
|
use psb_penv_mod
|
|
|
|
|
use psb_error_mod
|
|
|
|
|
use psb_realloc_mod
|
|
|
|
@ -890,17 +944,17 @@ contains
|
|
|
|
|
|
|
|
|
|
call idxmap%set_state(psb_desc_asb_)
|
|
|
|
|
|
|
|
|
|
end subroutine hash_asb
|
|
|
|
|
end subroutine hash_asb
|
|
|
|
|
|
|
|
|
|
function hash_get_fmt(idxmap) result(res)
|
|
|
|
|
function hash_get_fmt(idxmap) result(res)
|
|
|
|
|
implicit none
|
|
|
|
|
class(psb_hash_map), intent(in) :: idxmap
|
|
|
|
|
character(len=5) :: res
|
|
|
|
|
res = 'HASH'
|
|
|
|
|
end function hash_get_fmt
|
|
|
|
|
end function hash_get_fmt
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine hash_inner_cnvs1(x,hashmask,hashv,glb_lc,nrm)
|
|
|
|
|
subroutine hash_inner_cnvs1(x,hashmask,hashv,glb_lc,nrm)
|
|
|
|
|
|
|
|
|
|
integer, intent(in) :: hashmask,hashv(0:),glb_lc(:,:)
|
|
|
|
|
integer, intent(inout) :: x
|
|
|
|
@ -945,9 +999,9 @@ contains
|
|
|
|
|
else
|
|
|
|
|
x = tmp
|
|
|
|
|
end if
|
|
|
|
|
end subroutine hash_inner_cnvs1
|
|
|
|
|
end subroutine hash_inner_cnvs1
|
|
|
|
|
|
|
|
|
|
subroutine hash_inner_cnvs2(x,y,hashmask,hashv,glb_lc,nrm)
|
|
|
|
|
subroutine hash_inner_cnvs2(x,y,hashmask,hashv,glb_lc,nrm)
|
|
|
|
|
integer, intent(in) :: hashmask,hashv(0:),glb_lc(:,:)
|
|
|
|
|
integer, intent(in) :: x
|
|
|
|
|
integer, intent(out) :: y
|
|
|
|
@ -992,10 +1046,10 @@ contains
|
|
|
|
|
else
|
|
|
|
|
y = tmp
|
|
|
|
|
end if
|
|
|
|
|
end subroutine hash_inner_cnvs2
|
|
|
|
|
end subroutine hash_inner_cnvs2
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine hash_inner_cnv1(n,x,hashmask,hashv,glb_lc,mask,nrm)
|
|
|
|
|
subroutine hash_inner_cnv1(n,x,hashmask,hashv,glb_lc,mask,nrm)
|
|
|
|
|
integer, intent(in) :: n,hashmask,hashv(0:),glb_lc(:,:)
|
|
|
|
|
logical, intent(in), optional :: mask(:)
|
|
|
|
|
integer, intent(in), optional :: nrm
|
|
|
|
@ -1084,9 +1138,9 @@ contains
|
|
|
|
|
end if
|
|
|
|
|
end do
|
|
|
|
|
end if
|
|
|
|
|
end subroutine hash_inner_cnv1
|
|
|
|
|
end subroutine hash_inner_cnv1
|
|
|
|
|
|
|
|
|
|
subroutine hash_inner_cnv2(n,x,y,hashmask,hashv,glb_lc,mask,nrm)
|
|
|
|
|
subroutine hash_inner_cnv2(n,x,y,hashmask,hashv,glb_lc,mask,nrm)
|
|
|
|
|
integer, intent(in) :: n, hashmask,hashv(0:),glb_lc(:,:)
|
|
|
|
|
logical, intent(in), optional :: mask(:)
|
|
|
|
|
integer, intent(in), optional :: nrm
|
|
|
|
@ -1184,7 +1238,7 @@ contains
|
|
|
|
|
end if
|
|
|
|
|
end do
|
|
|
|
|
end if
|
|
|
|
|
end subroutine hash_inner_cnv2
|
|
|
|
|
end subroutine hash_inner_cnv2
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
end module psb_hash_map_mod
|
|
|
|
|