TABLE OF CONTENTS


ABINIT/m_hashtable [ Modules ]

[ Top ] [ Modules ]

NAME

 m_hashtable

FUNCTION

  A dictionary like structure for integers

COPYRIGHT

  Copyright (C) 2010-2024 ABINIT group (HM)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

SOURCE

 16 #if defined HAVE_CONFIG_H
 17 #include "config.h"
 18 #endif
 19 
 20 #include "abi_common.h"
 21 
 22 module m_hashtable
 23 
 24   use defs_basis
 25   use m_abicore
 26   implicit none
 27 
 28   type :: hashbucket
 29     integer :: nitems
 30     integer,allocatable :: items(:,:)
 31   end type hashbucket
 32 
 33   type :: hashtable_t
 34     integer :: bucketsize
 35     integer :: bucketstep
 36     integer :: nbuckets
 37     type(hashbucket),allocatable :: buckets(:)
 38   end type hashtable_t
 39 
 40   public :: hashtable_init
 41   public :: hashtable_add
 42   public :: hashtable_get
 43   public :: hashtable_cleanup
 44   public :: hashtable_items
 45   public :: hashtable_free
 46 
 47   contains
 48   type(hashtable_t) function hashtable_init(nbuckets,bucketsize,bucketstep) result(new)
 49     ! Create the hashtable structure
 50     integer,intent(in) :: bucketsize, bucketstep, nbuckets
 51     integer :: ibucket
 52 
 53     new%nbuckets = nbuckets
 54     new%bucketsize = bucketsize
 55     new%bucketstep = bucketstep
 56     ABI_MALLOC(new%buckets,(nbuckets))
 57     do ibucket=1,nbuckets
 58       ABI_MALLOC(new%buckets(ibucket)%items,(2,new%bucketsize))
 59       new%buckets(ibucket)%nitems = 0
 60     end do
 61   end function hashtable_init
 62 
 63   pure function compute_hash(self,key) result(ihash)
 64     type(hashtable_t),intent(in) :: self
 65     integer,intent(in) :: key
 66     integer :: ihash
 67     ihash = mod(key-1,self%nbuckets)+1
 68   end function compute_hash
 69 
 70   subroutine hashtable_add(self, key, val)
 71     ! Add a key to the hashtable structure
 72     type(hashtable_t) :: self
 73     integer,intent(in) :: key, val
 74     integer :: ihash, item, nitems
 75     integer,allocatable :: new_items(:,:)
 76     ! Compute bucket for this element
 77     ihash = compute_hash(self,key)
 78     nitems = self%buckets(ihash)%nitems
 79     ! Check if the element already exists in the bucket
 80     do item=1,nitems
 81       if (self%buckets(ihash)%items(1,item) /= key) cycle
 82       ! Replace value
 83       self%buckets(ihash)%items(2,item) = val
 84       return
 85     end do
 86     ! Check if the buckets are full
 87     if (size(self%buckets(ihash)%items,2)==nitems) then
 88       ABI_MALLOC(new_items,(2,nitems+self%bucketstep))
 89       new_items(:,:nitems) = self%buckets(ihash)%items(:,:nitems)
 90       new_items(:,nitems+1:) = 0
 91       ABI_MOVE_ALLOC(new_items,self%buckets(ihash)%items)
 92     end if
 93     ! Add the element to the bucket
 94     nitems = nitems + 1
 95     self%buckets(ihash)%items(:,nitems) = [key,val]
 96     self%buckets(ihash)%nitems = nitems
 97   end subroutine hashtable_add
 98 
 99   subroutine hashtable_print(self,iunit)
100     ! Print the hashtable data
101     type(hashtable_t),intent(in) :: self
102     integer,intent(in) :: iunit
103     integer :: ibucket,item
104     do ibucket=1,self%nbuckets
105       do item=1,self%buckets(ibucket)%nitems
106         write(iunit,*) ibucket, self%buckets(ibucket)%items(:,item)
107       end do
108     end do
109   end subroutine hashtable_print
110 
111   subroutine hashtable_get(self,key,val,ierr)
112     ! Get the value of a key in the hashtable
113     type(hashtable_t) :: self
114     integer,intent(in)  :: key
115     integer,intent(out) :: val,ierr
116     integer :: item, ihash
117     ierr = 0
118     ihash = compute_hash(self,key)
119     do item=1,self%buckets(ihash)%nitems
120       if (self%buckets(ihash)%items(1,item) /= key) cycle
121       val = self%buckets(ihash)%items(2,item)
122       return
123     end do
124     ierr = 1
125   end subroutine hashtable_get
126 
127   subroutine hashtable_items(self,items)
128     ! Get an array with all the keys in hashtable
129     type(hashtable_t) ::  self
130     integer :: item,ibucket,idx
131     integer,allocatable :: items(:,:)
132     ABI_MALLOC(items,(2,sum(self%buckets(:)%nitems)))
133     idx = 0
134     do ibucket=1,self%nbuckets
135       do item=1,self%buckets(ibucket)%nitems
136         idx = idx + 1
137         items(:,idx) = self%buckets(ibucket)%items(:,item)
138       end do
139     end do
140   end subroutine hashtable_items
141 
142   subroutine hashtable_cleanup(self)
143     ! Free up memory in all the buckets
144     ! this should be done only after all the add operations are finished
145     type(hashtable_t) ::  self
146     integer :: ibucket,nitems
147     integer,allocatable :: new_items(:,:)
148     do ibucket=1,self%nbuckets
149       ! get size of buckets and free unecessary memory
150       nitems = self%buckets(ibucket)%nitems
151       ABI_MALLOC(new_items,(2,nitems))
152       new_items = self%buckets(ibucket)%items(:,:nitems)
153       ABI_MOVE_ALLOC(new_items,self%buckets(ibucket)%items)
154     end do
155   end subroutine hashtable_cleanup
156 
157   integer function hashtable_size(self) result(bsize)
158     type(hashtable_t) ::  self
159     integer :: ibucket
160     ! Return the size of the hashtable in bytes
161     bsize = storage_size(self%buckets)*self%nbuckets
162     do ibucket=1,self%nbuckets
163       bsize = bsize + storage_size(self%buckets(ibucket)%items)*size(self%buckets(ibucket)%items,2)*2
164     end do
165     bsize = bsize/8
166   end function hashtable_size
167 
168   subroutine hashtable_free(self)
169     type(hashtable_t) ::  self
170     integer :: ibucket
171     if (allocated(self%buckets)) then
172       do ibucket=1,self%nbuckets
173         ABI_FREE(self%buckets(ibucket)%items)
174       end do
175       ABI_FREE(self%buckets)
176     end if
177   end subroutine hashtable_free
178 
179 end module m_hashtable