Skip to content

Commit 6aa5177

Browse files
authored
[hashmap] update initialization (#974)
2 parents 1ba499c + 2aae214 commit 6aa5177

21 files changed

+80
-64
lines changed

doc/specs/stdlib_hashmaps.md

+8-5
Original file line numberDiff line numberDiff line change
@@ -763,7 +763,7 @@ type. Each of these types are described below.
763763

764764
The `hashmap_type` abstract type serves as the parent type for the two
765765
types `chaining_hashmap_type` and `open_hashmap_type`. It defines
766-
seven private components:
766+
eight private components:
767767

768768
* `call_count` - the number of procedure calls on the map;
769769

@@ -782,6 +782,8 @@ seven private components:
782782

783783
* `hasher` - a pointer to the hash function used by the map.
784784

785+
* `initialized` - track if map has been initialized
786+
785787
It also defines five non-overridable procedures:
786788

787789
* `calls` - returns the number of procedure calls on the map;
@@ -1074,7 +1076,7 @@ are listed below.
10741076

10751077
Procedure to initialize a chaining hash map:
10761078

1077-
* `map % init( hasher[, slots_bits, status] )` - Routine
1079+
* `map % init( [hasher, slots_bits, status] )` - Routine
10781080
to initialize a chaining hash map.
10791081

10801082
Procedure to modify the structure of a map:
@@ -1295,7 +1297,7 @@ Initializes a `hashmap_type` object.
12951297

12961298
##### Syntax
12971299

1298-
`call map % ` [[hashmap_type(type):init(bound)]] `( hasher [, slots_bits, status ] )`
1300+
`call map % ` [[hashmap_type(type):init(bound)]] `( [hasher, slots_bits, status ] )`
12991301

13001302
##### Class
13011303

@@ -1308,9 +1310,10 @@ Subroutine
13081310
`intent(out)` argument. It will
13091311
be a hash map used to store and access the entries.
13101312

1311-
`hasher`: shall be a procedure with interface `hash_fun`.
1313+
`hasher`: (optional): shall be a procedure with interface `hash_fun`.
13121314
It is an `intent(in)` argument. It is the procedure to be used to
1313-
generate the hashes for the table from the keys of the entries.
1315+
generate the hashes for the table from the keys of the entries.
1316+
Defaults to fnv_1_hasher if not provided.
13141317

13151318
`slots_bits` (optional): shall be a scalar default integer
13161319
expression. It is an `intent(in)` argument. The initial number of
+1-2
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,9 @@
11
program example_calls
22
use stdlib_hashmaps, only: chaining_hashmap_type, int_calls
3-
use stdlib_hashmap_wrappers, only: fnv_1_hasher
43
implicit none
54
type(chaining_hashmap_type) :: map
65
integer(int_calls) :: initial_calls
7-
call map%init(fnv_1_hasher)
6+
call map%init()
87
initial_calls = map%calls()
98
print *, "INITIAL_CALLS = ", initial_calls
109
end program example_calls
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,9 @@
11
program example_entries
22
use stdlib_hashmaps, only: open_hashmap_type, int_index
3-
use stdlib_hashmap_wrappers, only: fnv_1_hasher
43
implicit none
54
type(open_hashmap_type) :: map
65
integer(int_index) :: initial_entries
7-
call map%init(fnv_1_hasher)
6+
call map%init()
87
initial_entries = map%entries()
98
print *, "INITIAL_ENTRIES = ", initial_entries
109
end program example_entries

example/hashmaps/example_hashmaps_get_all_keys.f90

+1-4
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,7 @@
11
program example_hashmaps_get_all_keys
22
use stdlib_kinds, only: int32
33
use stdlib_hashmaps, only: chaining_hashmap_type
4-
use stdlib_hashmap_wrappers, only: fnv_1_hasher, get, &
5-
key_type, set
4+
use stdlib_hashmap_wrappers, only: get, key_type, set
65
implicit none
76
type(chaining_hashmap_type) :: map
87
type(key_type) :: key
@@ -12,8 +11,6 @@ program example_hashmaps_get_all_keys
1211

1312
character(:), allocatable :: str
1413

15-
call map%init(fnv_1_hasher)
16-
1714
! adding key-value pairs to the map
1815
call set(key, "initial key")
1916
call map%map_entry(key, "value 1")

example/hashmaps/example_hashmaps_get_other_data.f90

+1-4
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
program example_get_other_data
22
use stdlib_kinds, only: int8, int64
33
use stdlib_hashmaps, only: chaining_hashmap_type, int_index
4-
use stdlib_hashmap_wrappers, only: fnv_1_hasher, key_type, set, get
4+
use stdlib_hashmap_wrappers, only: key_type, set
55
implicit none
66
logical :: conflict
77
type(key_type) :: key
@@ -14,9 +14,6 @@ program example_get_other_data
1414
integer(int8), allocatable :: key_array(:)
1515
integer :: int_scalar
1616

17-
! Initialize hashmap
18-
call map%init(fnv_1_hasher)
19-
2017
! Hashmap functions are setup to store scalar value types (other). Use a dervied
2118
! type wrapper to store arrays.
2219
dummy%value = [4, 3, 2, 1]
+21-2
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,26 @@
11
program example_init
2-
use stdlib_hashmaps, only: chaining_hashmap_type
2+
use stdlib_hashmaps, only: chaining_hashmap_type, open_hashmap_type
33
use stdlib_hashmap_wrappers, only: fnv_1_hasher
44
implicit none
55
type(chaining_hashmap_type) :: map
6-
call map%init(fnv_1_hasher, slots_bits=10)
6+
logical :: present
7+
8+
9+
!If default values are used, then init can be typically be skipped as the first map_entry call will initialize the map using default values.
10+
call map%map_entry('key', 'value')
11+
call map%key_test('key', present)
12+
print *, "Key exists without explicit init call = ", present
13+
14+
! Init can be called to clear all items in a map.
15+
call map%init()
16+
call map%key_test('key', present)
17+
print *, "Key exists after re-initalization = ", present
18+
19+
! User can optional specify hasher type and slots_bits instead of using default values.
20+
! Number of slots in the hashmap will initially equal 2**slots_bits.
21+
! The hashmap will automatically re-size as needed; however for better performance, a rule of thumb is to size so that number of slots is ~2X expected number of entries.
22+
! In this example with slots_bits=10, there will initially be 1024 slots in the map.
23+
call map%init(hasher=fnv_1_hasher, slots_bits=10)
24+
call map%map_entry('key', 'value')
25+
726
end program example_init
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,15 @@
11
program example_key_test
22
use stdlib_kinds, only: int8
33
use stdlib_hashmaps, only: chaining_hashmap_type
4-
use stdlib_hashmap_wrappers, only: fnv_1_hasher, key_type, set
4+
use stdlib_hashmap_wrappers, only: key_type, set
55
implicit none
66
type(chaining_hashmap_type) :: map
77
type(key_type) :: key
88
logical :: present
9-
call map%init(fnv_1_hasher)
9+
10+
call map%init()
1011
call set(key, [0_int8, 1_int8])
1112
call map%key_test(key, present)
1213
print *, "Initial key of 10 present for empty map = ", present
14+
1315
end program example_key_test
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,9 @@
11
program example_loading
22
use stdlib_hashmaps, only: open_hashmap_type
3-
use stdlib_hashmap_wrappers, only: fnv_1_hasher
43
implicit none
54
type(open_hashmap_type) :: map
65
real :: ratio
7-
call map%init(fnv_1_hasher)
6+
call map%init()
87
ratio = map%loading()
98
print *, "Initial loading = ", ratio
109
end program example_loading

example/hashmaps/example_hashmaps_map_entry.f90

+2-2
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
program example_map_entry
22
use, intrinsic:: iso_fortran_env, only: int8, int64
33
use stdlib_hashmaps, only: chaining_hashmap_type
4-
use stdlib_hashmap_wrappers, only: fnv_1_hasher, key_type, set
4+
use stdlib_hashmap_wrappers, only: key_type, set
55
implicit none
66
type(chaining_hashmap_type) :: map
77
type(key_type) :: key
@@ -16,7 +16,7 @@ program example_map_entry
1616

1717
! Initialize hashmap with 2^10 slots.
1818
! Hashmap will dynamically increase size if needed.
19-
call map%init(fnv_1_hasher, slots_bits=10)
19+
call map%init(slots_bits=10)
2020

2121
! Explicitly set key using set function
2222
call set(key, [1, 2, 3])
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,9 @@
11
program example_num_slots
22
use stdlib_hashmaps, only: chaining_hashmap_type, int_index
3-
use stdlib_hashmap_wrappers, only: fnv_1_hasher
43
implicit none
54
type(chaining_hashmap_type) :: map
65
integer(int_index) :: initial_slots
7-
call map%init(fnv_1_hasher)
6+
call map%init()
87
initial_slots = map%num_slots()
98
print *, "Initial slots = ", initial_slots
109
end program example_num_slots
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,9 @@
11
program example_probes
22
use stdlib_hashmaps, only: chaining_hashmap_type
3-
use stdlib_hashmap_wrappers, only: fnv_1_hasher
43
implicit none
54
type(chaining_hashmap_type) :: map
65
integer :: nprobes
7-
call map%init(fnv_1_hasher)
6+
call map%init()
87
nprobes = map%map_probes()
98
print *, "Initial probes = ", nprobes
109
end program example_probes

example/hashmaps/example_hashmaps_rehash.f90

+2-2
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,12 @@
11
program example_rehash
22
use stdlib_kinds, only: int8
33
use stdlib_hashmaps, only: open_hashmap_type
4-
use stdlib_hashmap_wrappers, only: fnv_1_hasher, fnv_1a_hasher, &
4+
use stdlib_hashmap_wrappers, only: fnv_1a_hasher, &
55
key_type, set
66
implicit none
77
type(open_hashmap_type) :: map
88
type(key_type) :: key
9-
call map%init(fnv_1_hasher, slots_bits=10)
9+
call map%init(slots_bits=10)
1010
call set(key, [5_int8, 7_int8, 4_int8, 13_int8])
1111
call map%map_entry(key, 'A value')
1212
call map%rehash(fnv_1a_hasher)

example/hashmaps/example_hashmaps_remove.f90

+2-3
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,7 @@
11
program example_remove
22
use stdlib_kinds, only: int8, int64
33
use stdlib_hashmaps, only: open_hashmap_type
4-
use stdlib_hashmap_wrappers, only: fnv_1_hasher, &
5-
fnv_1a_hasher, key_type, set
4+
use stdlib_hashmap_wrappers, only: key_type, set
65
implicit none
76
type(open_hashmap_type) :: map
87
type(key_type) :: key
@@ -11,7 +10,7 @@ program example_remove
1110

1211
! Initialize hashmap with 2^10 slots.
1312
! Hashmap will dynamically increase size if needed.
14-
call map%init(fnv_1_hasher, slots_bits=10)
13+
call map%init(slots_bits=10)
1514
! Explicitly set key type using set function
1615
call set(key, [1, 2, 3])
1716
call map%map_entry(key, 4.0)

example/hashmaps/example_hashmaps_set_other_data.f90

+2-2
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
program example_set_other_data
22
use stdlib_kinds, only: int8
33
use stdlib_hashmaps, only: open_hashmap_type, chaining_hashmap_type
4-
use stdlib_hashmap_wrappers, only: key_type, set, fnv_1_hasher
4+
use stdlib_hashmap_wrappers, only: key_type, set
55

66
implicit none
77
logical :: exists
@@ -11,7 +11,7 @@ program example_set_other_data
1111

1212
! Initialize hashmap with 2^10 slots.
1313
! Hashmap will dynamically increase size if needed.
14-
call map%init(fnv_1_hasher, slots_bits=10)
14+
call map%init(slots_bits=10)
1515

1616
call set(key, [5, 7, 4, 13])
1717

Original file line numberDiff line numberDiff line change
@@ -1,10 +1,9 @@
11
program example_slots_bits
22
use stdlib_hashmaps, only: chaining_hashmap_type
3-
use stdlib_hashmap_wrappers, only: fnv_1_hasher
43
implicit none
54
type(chaining_hashmap_type) :: map
65
integer :: bits
7-
call map%init(fnv_1_hasher)
6+
call map%init()
87
bits = map%slots_bits()
98
print *, "Initial slot bits = ", bits
109
end program example_slots_bits
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,9 @@
11
program example_total_depth
22
use stdlib_hashmaps, only: chaining_hashmap_type, int_depth
3-
use stdlib_hashmap_wrappers, only: fnv_1_hasher
43
implicit none
54
type(chaining_hashmap_type) :: map
65
integer(int_depth) :: initial_depth
7-
call map%init(fnv_1_hasher)
6+
call map%init()
87
initial_depth = map%total_depth()
98
print *, "Initial total depth = ", initial_depth
109
end program example_total_depth

src/stdlib_hashmap_chaining.f90

+9-3
Original file line numberDiff line numberDiff line change
@@ -434,7 +434,7 @@ module subroutine init_chaining_map( map, &
434434
!! greater than max_bits
435435
!
436436
class(chaining_hashmap_type), intent(out) :: map
437-
procedure(hasher_fun) :: hasher
437+
procedure(hasher_fun), optional :: hasher
438438
integer, intent(in), optional :: slots_bits
439439
integer(int32), intent(out), optional :: status
440440

@@ -448,8 +448,9 @@ module subroutine init_chaining_map( map, &
448448
map % probe_count = 0
449449
map % total_probes = 0
450450

451-
map % hasher => hasher
452-
451+
! Check if user has specified a hasher other than the default hasher.
452+
if (present(hasher)) map % hasher => hasher
453+
453454
call free_chaining_map( map )
454455

455456
if ( present(slots_bits) ) then
@@ -502,6 +503,8 @@ module subroutine init_chaining_map( map, &
502503

503504
call extend_map_entry_pool(map)
504505

506+
map % initialized = .true.
507+
505508
if (present(status) ) status = success
506509

507510
end subroutine init_chaining_map
@@ -545,6 +548,9 @@ module subroutine map_chain_entry(map, key, other, conflict)
545548
type(chaining_map_entry_type), pointer :: gentry, pentry, sentry
546549
character(*), parameter :: procedure = 'MAP_ENTRY'
547550

551+
! Check that map is initialized.
552+
if (.not. map % initialized) call init_chaining_map( map )
553+
548554
hash_val = map % hasher( key )
549555

550556
if ( map % probe_count > map_probe_factor * map % call_count ) then

src/stdlib_hashmap_open.f90

+10-4
Original file line numberDiff line numberDiff line change
@@ -410,7 +410,7 @@ module subroutine init_open_map( map, &
410410
!! greater than max_bits
411411

412412
class(open_hashmap_type), intent(out) :: map
413-
procedure(hasher_fun) :: hasher
413+
procedure(hasher_fun), optional :: hasher
414414
integer, intent(in), optional :: slots_bits
415415
integer(int32), intent(out), optional :: status
416416

@@ -424,8 +424,9 @@ module subroutine init_open_map( map, &
424424
map % call_count = 0
425425
map % probe_count = 0
426426
map % total_probes = 0
427-
428-
map % hasher => hasher
427+
428+
! Check if user has specified a hasher other than the default hasher.
429+
if (present(hasher)) map % hasher => hasher
429430

430431
if ( present(slots_bits) ) then
431432
if ( slots_bits < default_bits .OR. &
@@ -491,6 +492,8 @@ module subroutine init_open_map( map, &
491492
end do
492493

493494
call extend_map_entry_pool(map % cache)
495+
496+
map % initialized = .true.
494497

495498
if (present(status) ) status = success
496499

@@ -533,7 +536,10 @@ module subroutine map_open_entry(map, key, other, conflict)
533536
integer(int_hash) :: hash_val
534537
integer(int_index) :: inmap, offset, test_slot
535538
character(*), parameter :: procedure = 'MAP_ENTRY'
536-
539+
540+
! Check that map is initialized.
541+
if (.not. map % initialized) call init_open_map( map )
542+
537543
hash_val = map % hasher( key )
538544

539545
if ( map % probe_count > map_probe_factor * map % call_count .or. &

0 commit comments

Comments
 (0)