Skip to content

Commit f705430

Browse files
authored
Merge pull request #13 from jvdp1/hash_maps_review
Some additions to hash maps
2 parents dd120fe + 45b92c7 commit f705430

File tree

3 files changed

+47
-8
lines changed

3 files changed

+47
-8
lines changed

doc/specs/stdlib_hashmaps.md

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,7 @@ The module `stdlib_hashmaps` defines the API for a parent datatype,
5353
`hashmap_type` and two extensions of that hash map type:
5454
`chaining_hashmap_type` and `open_hashmap_type`.
5555

56-
The `hashmap_type` defines the Application Programers
56+
The `hashmap_type` defines the Application Programmers
5757
Interface (API) for the procedures used by its two extensions. It
5858
explicitly defines five non-overridable procedures. It also defines
5959
the interfaces for eleven deferred procedures. It does not define the
@@ -113,7 +113,7 @@ keys and their associated data.
113113

114114
The constant `int_hash` is used to define the integer kind value for
115115
the returned hash codes and variables used to access them. It
116-
currently is imported from `stdlib_hash_32bit` where it haas the
116+
currently is imported from `stdlib_hash_32bit` where it has the
117117
value, `int32`.
118118

119119
### The `stdlib_hashmap_wrappers`' module's derived types
@@ -229,7 +229,7 @@ is an `intent(out)` argument.
229229
```fortran
230230
program demo_copy_key
231231
use stdlib_hashmap_wrappers, only: &
232-
copy_key, operator(==), equal_keys, key_type
232+
copy_key, operator(==), key_type
233233
use iso_fortran_env, only: int8
234234
implicit none
235235
integer(int8) :: i, value(15)
@@ -1043,7 +1043,7 @@ seven private components:
10431043

10441044
* `nbits` - the number of bits used to address the slots;
10451045

1046-
* `num_entries` - the humber of entries in the map;
1046+
* `num_entries` - the number of entries in the map;
10471047

10481048
* `num_free` - the number of entries in the free list of removed
10491049
entries;
@@ -1609,7 +1609,7 @@ entry in the map.
16091609

16101610
##### Syntax
16111611

1612-
`result = call map % [[hashmap_type(type):key_test(bound)]]( key, present )`
1612+
`call map % [[hashmap_type(type):key_test(bound)]]( key, present )`
16131613

16141614
##### Class
16151615

src/stdlib_hashmap_wrappers.f90

Lines changed: 18 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -110,7 +110,9 @@ end function hasher_fun
110110
pure subroutine copy_key( old_key, new_key )
111111
!! Version: Experimental
112112
!!
113-
!! Copies the contents of the key, old_key, to the key, out_key
113+
!! Copies the contents of the key, old_key, to the key, new_key
114+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#copy_key-returns-a-copy-of-the-key))
115+
!!
114116
!! Arguments:
115117
!! old_key - the input key
116118
!! new_key - the output copy of old_key
@@ -126,6 +128,8 @@ subroutine copy_other( other_in, other_out )
126128
!! Version: Experimental
127129
!!
128130
!! Copies the other data, other_in, to the variable, other_out
131+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#copy_other-returns-a-copy-of-the-other-data))
132+
!!
129133
!! Arguments:
130134
!! other_in - the input data
131135
!! other_out - the output data
@@ -141,6 +145,8 @@ function equal_keys( key1, key2 ) result(test) ! Chase's tester
141145
!! Version: Experimental
142146
!!
143147
!! Compares two keys for equality
148+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#operator(==)-compares-two-keys-for-equality))
149+
!!
144150
!! Arguments:
145151
!! key1 - the first key
146152
!! key2 - the second key
@@ -167,6 +173,8 @@ subroutine free_key( key )
167173
!! Version: Experimental
168174
!!
169175
!! Frees the memory in a key
176+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#free_key-frees-the-memory-associated-with-a-key))
177+
!!
170178
!! Arguments:
171179
!! key - the key
172180
type(key_type), intent(inout) :: key
@@ -180,6 +188,8 @@ subroutine free_other( other )
180188
!! Version: Experimental
181189
!!
182190
!! Frees the memory in the other data
191+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#free_other-frees-the-memory-associated-with-other-data))
192+
!!
183193
!! Arguments:
184194
!! other - the other data
185195
type(other_type), intent(inout) :: other
@@ -330,6 +340,8 @@ pure function fnv_1a_hasher( key )
330340
!! Version: Experimental
331341
!!
332342
!! Hashes a key with the FNV_1a algorithm
343+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#fnv_1a_hasher-calculates-a-hash-code-from-a-key))
344+
!!
333345
!! Arguments:
334346
!! key - the key to be hashed
335347
type(key_type), intent(in) :: key
@@ -344,6 +356,8 @@ pure function seeded_nmhash32_hasher( key )
344356
!! Version: Experimental
345357
!!
346358
!! Hashes a key with the NMHASH32 hash algorithm
359+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#seeded_nmhash32_hasher-calculates-a-hash-code-from-a-key))
360+
!!
347361
!! Arguments:
348362
!! key - the key to be hashed
349363
!! seed - the seed (unused) for the hashing algorithm
@@ -360,6 +374,7 @@ pure function seeded_nmhash32x_hasher( key )
360374
!! Version: Experimental
361375
!!
362376
!! Hashes a key with the NMHASH32X hash algorithm
377+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#seeded_nmhash32x_hasher-calculates-a-hash-code-from-a-key))
363378
!! Arguments:
364379
!! key - the key to be hashed
365380
!! seed - the seed (unused) for the hashing algorithm
@@ -376,6 +391,8 @@ pure function seeded_water_hasher( key )
376391
!! Version: Experimental
377392
!!
378393
!! Hashes a key with the waterhash algorithm
394+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#seeded_water_hasher-calculates-a-hash-code-from-a-key))
395+
!!
379396
!! Arguments:
380397
!! key - the key to be hashed
381398
type(key_type), intent(in) :: key

src/stdlib_hashmaps.f90

Lines changed: 24 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -70,6 +70,7 @@ module stdlib_hashmaps
7070
!! Version: Experimental
7171
!!
7272
!! Type implementing an abstract hash map
73+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#the-hashmap_type-abstract-type))
7374
private
7475
integer(int_calls) :: call_count = 0
7576
!! Number of calls
@@ -158,6 +159,8 @@ subroutine key_test(map, key, present)
158159
!! Version: Experimental
159160
!!
160161
!! Returns a logical flag indicating whether KEY exists in the hash map
162+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#key_test-indicates-whether-key-is-present))
163+
!!
161164
!! Arguments:
162165
!! map - the hash map of interest
163166
!! key - the key of interest
@@ -173,6 +176,8 @@ pure function loading( map )
173176
!! Version: Experimental
174177
!!
175178
!! Returns the number of entries relative to slots in a hash map
179+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#loading-returns-the-ratio-of-entries-to-slots))
180+
!!
176181
!! Arguments:
177182
!! map - a hash map
178183
import hashmap_type
@@ -184,8 +189,8 @@ subroutine map_entry(map, key, other, conflict)
184189
!! Version: Experimental
185190
!!
186191
!! Inserts an entry into the hash table
187-
!! Arguments:
188-
!
192+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#map_entry-inserts-an-entry-into-the-hash-map))
193+
!!
189194
import hashmap_type, key_type, other_type
190195
class(hashmap_type), intent(inout) :: map
191196
type(key_type), intent(in) :: key
@@ -246,6 +251,7 @@ function total_depth( map )
246251
!!
247252
!! Returns the total number of ones based offsets of slot entriesyy from
248253
!! their slot index for a hash map
254+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#total_depth-returns-the-total-depth-of-the-hash-map-entries))
249255
!! Arguments:
250256
!! map - a hash map
251257
import hashmap_type, int64
@@ -261,6 +267,7 @@ end function total_depth
261267
!! Version: Experimental
262268
!!
263269
!! Chaining hash map entry type
270+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#the-chaining_map_entry_type-derived-type))
264271
private
265272
integer(int_hash) :: hash_val
266273
!! Full hash value
@@ -279,6 +286,7 @@ end function total_depth
279286
!! Version: Experimental
280287
!!
281288
!! Wrapper for a pointer to a chaining map entry type object
289+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#the-chaining_map_entry_type_ptr-derived-type))
282290
type(chaining_map_entry_type), pointer :: target => null()
283291
end type chaining_map_entry_ptr
284292

@@ -287,6 +295,7 @@ end function total_depth
287295
!! Version: Experimental
288296
!!
289297
!! Type implementing a pool of allocated `chaining_map_entry_type`
298+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#the-chaining_map_entry_pool-derived-type))
290299
private
291300
! Index of next bucket
292301
integer(int_index) :: next = 0
@@ -299,6 +308,7 @@ end function total_depth
299308
!! Version: Experimental
300309
!!
301310
!! Type implementing the `chaining_hashmap_type` types
311+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#the-chaining_hashmap_type-derived-type))
302312
private
303313
type(chaining_map_entry_pool), pointer :: cache => null()
304314
!! Pool of allocated chaining_map_entry_type objects
@@ -487,6 +497,7 @@ end function total_chaining_depth
487497
!! Version: Experimental
488498
!!
489499
!! Open hash map entry type
500+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#the-open_map_entry_type-derived-type))
490501
private
491502
integer(int_hash) :: hash_val
492503
!! Full hash value
@@ -512,6 +523,7 @@ end function total_chaining_depth
512523
!! Version: Experimental
513524
!!
514525
!! Wrapper for a pointer to an open hash map entry type object
526+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#the-open_map_entry_ptr-derived-type))
515527
type(open_map_entry_type), pointer :: target => null()
516528
end type open_map_entry_ptr
517529

@@ -720,6 +732,8 @@ pure function calls( map )
720732
!! Version: Experimental
721733
!!
722734
!! Returns the number of subroutine calls on an open hash map
735+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#calls-returns-the-number-of-calls-on-the-hash-map))
736+
!!
723737
!! Arguments:
724738
!! map - an open hash map
725739
class(hashmap_type), intent(in) :: map
@@ -733,6 +747,8 @@ pure function entries( map )
733747
!! Version: Experimental
734748
!!
735749
!! Returns the number of entries in a hash map
750+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#entries-returns-the-number-of-entries-in-the-hash-map))
751+
!!
736752
!! Arguments:
737753
!! map - an open hash map
738754
class(hashmap_type), intent(in) :: map
@@ -747,6 +763,8 @@ pure function map_probes( map )
747763
!! Version: Experimental
748764
!!
749765
!! Returns the total number of table probes on a hash map
766+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#map_probes-returns-the-number-of-hash-map-probes))
767+
!!
750768
!! Arguments:
751769
!! map - an open hash map
752770
class(hashmap_type), intent(in) :: map
@@ -761,6 +779,8 @@ pure function num_slots( map )
761779
!! Version: Experimental
762780
!!
763781
!! Returns the number of allocated slots in a hash map
782+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#num_slots-returns-the-number-of-hash-map-slots))
783+
!!
764784
!! Arguments:
765785
!! map - an open hash map
766786
class(hashmap_type), intent(in) :: map
@@ -776,6 +796,8 @@ pure function slots_bits( map )
776796
!!
777797
!! Returns the number of bits used to specify the number of allocated
778798
!! slots in a hash map
799+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#slots_bits-returns-the-number-of-bits-used-to-address-the-hash-map-slots))
800+
!!
779801
!! Arguments:
780802
!! map - an open hash map
781803
class(hashmap_type), intent(in) :: map

0 commit comments

Comments
 (0)