Giter Site home page Giter Site logo

Comments (8)

gareth-nx avatar gareth-nx commented on September 25, 2024 1

I have limited knowledge of hash maps, but am puzzled by this small modification of @jannisteunissen's program.

If replace the open_hashmap_type with a chaining_hashmap_type then the speed is significantly faster, but the program fails at the error stop.

From inspection, it seems that for chaining_hashmap_type a call to map%remove() does not always lead to map%entries() being reduced by 1. Whereas that does happen for the open_hashmap_type.

Does anyone know if this is expected? @wclodius2

program chaining_hashmap_benchmark
  use stdlib_kinds, only: dp, int8, int32
  use stdlib_hashmaps, only : open_hashmap_type, chaining_hashmap_type
  use stdlib_hashmap_wrappers

  implicit none

  !! Choice of hashmap -- should these do the same thing? 
  !type(open_hashmap_type)     :: map 
  type(chaining_hashmap_type)     :: map

  integer, parameter          :: n_max = 5*1000*1000
  integer                     :: n
  integer(int32), allocatable :: keys(:)
  integer, allocatable        :: key_counts(:)
  real(dp)                    :: t_start, t_end
  real(dp), allocatable       :: r_uniform(:)
  type(key_type)              :: key
  logical                     :: present
  integer(int8)               :: int32_as_int8(4)

  call map%init(fnv_1_hasher, slots_bits=10)

  allocate(keys(n_max), r_uniform(n_max))

  call random_number(r_uniform)
  keys = nint(r_uniform * n_max * 0.25_dp)

  call cpu_time(t_start)
  do n = 1, n_max
     int32_as_int8 = transfer(keys(n), int32_as_int8)
     call set(key, int32_as_int8)

     call map%key_test(key, present)

     if (present) then
        !print*, map%entries()
        call map%remove(key)
        !print*, map%entries() ! Did this reduce?
     else
        call map%map_entry(key)
     end if
  end do
  call cpu_time(t_end)

  write(*, "(A,E12.4)") "Elapsed time (s) ", t_end - t_start
  write(*, "(A,E12.4)") "Entries/s        ", n_max/(t_end - t_start)
  write(*, "(A,I12)")   "n_occupied       ", map%entries()
  write(*, "(A,I12)")   "n_buckets        ", map%num_slots()

  ! Count number of keys that occur an odd number of times
  allocate(key_counts(minval(keys):maxval(keys)))
  key_counts = 0
  do n = 1, n_max
     key_counts(keys(n)) = key_counts(keys(n)) + 1
  end do
  n = sum(iand(key_counts, 1))

  if (n /= map%entries()) then
     error stop "FAILED"
  else
     print *, "PASSED"
  end if

  ! Clean up allocated storage
  deallocate(key_counts)

end program chaining_hashmap_benchmark

from stdlib.

gareth-nx avatar gareth-nx commented on September 25, 2024 1

@jvdp1 I was just looking at this, and found that if we append the line

map % num_entries = map % num_entries - 1

right at the end of remove_chaining_entry, then the test passes, while the speed remains much better than for open_hashmap_type.

I guess we need to add some additional tests of the hashmaps!

from stdlib.

jannisteunissen avatar jannisteunissen commented on September 25, 2024 1

Glad to see that this test was also useful in other ways! I'd be happy to contribute it to to the test suite. Let me also mention that the code I compared with used open addressing (and quadratic probing), so in principle better performance should be possible for open_hashmap_type.

from stdlib.

jvdp1 avatar jvdp1 commented on September 25, 2024

Thank you @jannisteunissen for this report. I tested your code on my machine, and I got similar results with gfortran and the fpm options used with the profile release. I tested other hashers and got similar times.

from stdlib.

gareth-nx avatar gareth-nx commented on September 25, 2024

@wclodius2

from stdlib.

jvdp1 avatar jvdp1 commented on September 25, 2024

@gareth-nx I spotted the same issue, and plan to submit a PR soon to fix it.

from stdlib.

wclodius2 avatar wclodius2 commented on September 25, 2024

from stdlib.

gareth-nx avatar gareth-nx commented on September 25, 2024

No problem at all @wclodius2 -- enjoy your vacation -- and please don't feel obliged to respond unless you feel like it.

from stdlib.

Related Issues (20)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.