Skip to content

Commit b8fbb3c

Browse files
authored
Merge pull request #741 from degawa/hashmap-get-all-keys
Added a procedure for getting all the keys in a hashmap
2 parents 4204079 + b083fc7 commit b8fbb3c

8 files changed

+286
-1
lines changed

doc/specs/stdlib_hashmaps.md

+45-1
Original file line numberDiff line numberDiff line change
@@ -890,7 +890,10 @@ It also defines five non-overridable procedures:
890890
* `num_slots` - returns the number of slots in the map; and
891891

892892
* `slots_bits` - returns the number of bits used to address the slots;
893-
and eleven deferred procedures:
893+
894+
and ten deferred procedures:
895+
896+
* `get_all_keys` - gets all the keys contained in a map;
894897

895898
* `get_other_data` - gets the other map data associated with the key;
896899

@@ -932,6 +935,7 @@ The type's definition is below:
932935
procedure, non_overridable, pass(map) :: map_probes
933936
procedure, non_overridable, pass(map) :: slots_bits
934937
procedure, non_overridable, pass(map) :: num_slots
938+
procedure(get_all_keys), deferred, pass(map) :: get_all_keys
935939
procedure(get_other), deferred, pass(map) :: get_other_data
936940
procedure(init_map), deferred, pass(map) :: init
937941
procedure(key_test), deferred, pass(map) :: key_test
@@ -1026,6 +1030,7 @@ as follows:
10261030
type(chaining_map_entry_ptr), allocatable :: inverse(:)
10271031
type(chaining_map_entry_ptr), allocatable :: slots(:)
10281032
contains
1033+
procedure :: get_all_keys => get_all_chaining_keys
10291034
procedure :: get_other_data => get_other_chaining_data
10301035
procedure :: init => init_chaining_map
10311036
procedure :: key => chaining_key_test
@@ -1103,6 +1108,7 @@ as follows:
11031108
type(open_map_entry_ptr), allocatable :: inverse(:)
11041109
integer(int_index), allocatable :: slots(:)
11051110
contains
1111+
procedure :: get_all_keys => get_all_open_keys
11061112
procedure :: get_other_data => get_other_open_data
11071113
procedure :: init => init_open_map
11081114
procedure :: key_test => open_key_test
@@ -1148,6 +1154,9 @@ Procedures to modify the content of a map:
11481154

11491155
Procedures to report the content of a map:
11501156

1157+
* `map % get_all_keys( all_keys )` - Returns all the keys
1158+
contained in the map;
1159+
11511160
* `map % get_other_data( key, other, exists )` - Returns the other data
11521161
associated with the `key`;
11531162

@@ -1251,6 +1260,41 @@ The result will be the number of entries in the hash map.
12511260
```
12521261

12531262

1263+
#### `get_all_keys` - Returns all the keys contained in a map
1264+
1265+
##### Status
1266+
1267+
Experimental
1268+
1269+
##### Description
1270+
1271+
Returns all the keys contained in a map.
1272+
1273+
##### Syntax
1274+
1275+
`call map % [[hashmap_type(type):get_all_keys(bound)]]( all_keys )`
1276+
1277+
##### Class
1278+
1279+
Subroutine
1280+
1281+
##### Arguments
1282+
1283+
`map` (pass): shall be a scalar variable of class
1284+
`chaining_hashmap_type` or `open_hashmap_type`. It is an
1285+
`intent(in)` argument. It will be
1286+
the hash map used to store and access the other data.
1287+
1288+
`all_keys`: shall be a rank-1 allocatable array of type `key_type`.
1289+
It is an `intent(out)` argument.
1290+
1291+
##### Example
1292+
1293+
```fortran
1294+
{!example/hashmaps/example_hashmaps_get_all_keys.f90!}
1295+
```
1296+
1297+
12541298
#### `get_other_data` - Returns other data associated with the `key`
12551299

12561300
##### Status

example/hashmaps/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ ADD_EXAMPLE(hashmaps_fnv_1_hasher)
88
ADD_EXAMPLE(hashmaps_free_key)
99
ADD_EXAMPLE(hashmaps_free_other)
1010
ADD_EXAMPLE(hashmaps_get)
11+
ADD_EXAMPLE(hashmaps_get_all_keys)
1112
ADD_EXAMPLE(hashmaps_get_other_data)
1213
ADD_EXAMPLE(hashmaps_hasher_fun)
1314
ADD_EXAMPLE(hashmaps_init)
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,52 @@
1+
program example_hashmaps_get_all_keys
2+
use stdlib_kinds, only: int32
3+
use stdlib_hashmaps, only: chaining_hashmap_type
4+
use stdlib_hashmap_wrappers, only: fnv_1_hasher, &
5+
key_type, other_type, set
6+
implicit none
7+
type(chaining_hashmap_type) :: map
8+
type(key_type) :: key
9+
type(other_type) :: other
10+
11+
type(key_type), allocatable :: keys(:)
12+
integer(int32) :: i
13+
14+
call map%init(fnv_1_hasher)
15+
16+
! adding key-value pairs to the map
17+
call set(key, "initial key")
18+
call set(other, "value 1")
19+
call map%map_entry(key, other)
20+
21+
call set(key, "second key")
22+
call set(other, "value 2")
23+
call map%map_entry(key, other)
24+
25+
call set(key, "last key")
26+
call set(other, "value 3")
27+
call map%map_entry(key, other)
28+
29+
! getting all the keys in the map
30+
call map%get_all_keys(keys)
31+
32+
print '("Number of keys in the hashmap = ", I0)', size(keys)
33+
!Number of keys in the hashmap = 3
34+
35+
do i = 1, size(keys)
36+
print '("Value of key ", I0, " = ", A)', i, key_to_char(keys(i))
37+
end do
38+
!Value of key 1 = initial key
39+
!Value of key 2 = second key
40+
!Value of key 3 = last key
41+
42+
contains
43+
!Converts key type to character type
44+
pure function key_to_char(key) result(str)
45+
type(key_type), intent(in) :: key
46+
character(:), allocatable :: str
47+
character(:), allocatable :: str_mold
48+
49+
allocate( character(len=size(key%value)) :: str_mold )
50+
str = transfer(key%value, str_mold)
51+
end function key_to_char
52+
end program example_hashmaps_get_all_keys

src/stdlib_hashmap_chaining.f90

+31
Original file line numberDiff line numberDiff line change
@@ -284,6 +284,37 @@ recursive subroutine free_map_entry_pool(pool) ! gent_pool_free
284284
end subroutine free_map_entry_pool
285285

286286

287+
module subroutine get_all_chaining_keys(map, all_keys)
288+
!! Version: Experimental
289+
!!
290+
!! Returns all the keys contained in a hash map
291+
!! Arguments:
292+
!! map - a chaining hash map
293+
!! all_keys - all the keys contained in a hash map
294+
!
295+
class(chaining_hashmap_type), intent(in) :: map
296+
type(key_type), allocatable, intent(out) :: all_keys(:)
297+
298+
integer(int32) :: num_keys
299+
integer(int_index) :: i, key_idx
300+
301+
num_keys = map % entries()
302+
allocate( all_keys(num_keys) )
303+
if ( num_keys == 0 ) return
304+
305+
if( allocated( map % inverse ) ) then
306+
key_idx = 1_int_index
307+
do i=1_int_index, size( map % inverse, kind=int_index )
308+
if ( associated( map % inverse(i) % target ) ) then
309+
all_keys(key_idx) = map % inverse(i) % target % key
310+
key_idx = key_idx + 1_int_index
311+
end if
312+
end do
313+
end if
314+
315+
end subroutine get_all_chaining_keys
316+
317+
287318
module subroutine get_other_chaining_data( map, key, other, exists )
288319
!! Version: Experimental
289320
!!

src/stdlib_hashmap_open.f90

+31
Original file line numberDiff line numberDiff line change
@@ -254,6 +254,37 @@ module subroutine free_open_map( map )
254254
end subroutine free_open_map
255255

256256

257+
module subroutine get_all_open_keys(map, all_keys)
258+
!! Version: Experimental
259+
!!
260+
!! Returns all the keys contained in a hash map
261+
!! Arguments:
262+
!! map - an open hash map
263+
!! all_keys - all the keys contained in a hash map
264+
!
265+
class(open_hashmap_type), intent(in) :: map
266+
type(key_type), allocatable, intent(out) :: all_keys(:)
267+
268+
integer(int32) :: num_keys
269+
integer(int_index) :: i, key_idx
270+
271+
num_keys = map % entries()
272+
allocate( all_keys(num_keys) )
273+
if ( num_keys == 0 ) return
274+
275+
if ( allocated( map % inverse) ) then
276+
key_idx = 1_int_index
277+
do i=1_int_index, size( map % inverse, kind=int_index )
278+
if ( associated( map % inverse(i) % target ) ) then
279+
all_keys(key_idx) = map % inverse(i) % target % key
280+
key_idx = key_idx + 1_int_index
281+
end if
282+
end do
283+
end if
284+
285+
end subroutine get_all_open_keys
286+
287+
257288
module subroutine get_other_open_data( map, key, other, exists )
258289
!! Version: Experimental
259290
!!

src/stdlib_hashmaps.f90

+44
Original file line numberDiff line numberDiff line change
@@ -94,6 +94,7 @@ module stdlib_hashmaps
9494
procedure, non_overridable, pass(map) :: map_probes
9595
procedure, non_overridable, pass(map) :: num_slots
9696
procedure, non_overridable, pass(map) :: slots_bits
97+
procedure(get_all_keys), deferred, pass(map) :: get_all_keys
9798
procedure(get_other), deferred, pass(map) :: get_other_data
9899
procedure(init_map), deferred, pass(map) :: init
99100
procedure(key_test), deferred, pass(map) :: key_test
@@ -109,6 +110,21 @@ module stdlib_hashmaps
109110

110111
abstract interface
111112

113+
subroutine get_all_keys(map, all_keys)
114+
!! Version: Experimental
115+
!!
116+
!! Returns the all keys contained in a hash map
117+
!! ([Specifications](../page/specs/stdlib_hashmaps.html#get_all_keys-returns-all-the-keys-contained-in-a-map))
118+
!!
119+
!! Arguments:
120+
!! map - a hash map
121+
!! all_keys - all the keys contained in a hash map
122+
!
123+
import hashmap_type, key_type
124+
class(hashmap_type), intent(in) :: map
125+
type(key_type), allocatable, intent(out) :: all_keys(:)
126+
end subroutine get_all_keys
127+
112128
subroutine get_other( map, key, other, exists )
113129
!! Version: Experimental
114130
!!
@@ -319,6 +335,7 @@ end function total_depth
319335
type(chaining_map_entry_ptr), allocatable :: slots(:)
320336
!! Array of bucket lists Note # slots=size(slots)
321337
contains
338+
procedure :: get_all_keys => get_all_chaining_keys
322339
procedure :: get_other_data => get_other_chaining_data
323340
procedure :: init => init_chaining_map
324341
procedure :: loading => chaining_loading
@@ -345,6 +362,19 @@ module subroutine free_chaining_map( map )
345362
end subroutine free_chaining_map
346363

347364

365+
module subroutine get_all_chaining_keys(map, all_keys)
366+
!! Version: Experimental
367+
!!
368+
!! Returns all the keys contained in a hashmap
369+
!! Arguments:
370+
!! map - an chaining hash map
371+
!! all_keys - all the keys contained in a hash map
372+
!
373+
class(chaining_hashmap_type), intent(in) :: map
374+
type(key_type), allocatable, intent(out) :: all_keys(:)
375+
end subroutine get_all_chaining_keys
376+
377+
348378
module subroutine get_other_chaining_data( map, key, other, exists )
349379
!! Version: Experimental
350380
!!
@@ -556,6 +586,7 @@ end function total_chaining_depth
556586
integer(int_index), allocatable :: slots(:)
557587
!! Array of indices to the inverse Note # slots=size(slots)
558588
contains
589+
procedure :: get_all_keys => get_all_open_keys
559590
procedure :: get_other_data => get_other_open_data
560591
procedure :: init => init_open_map
561592
procedure :: loading => open_loading
@@ -581,6 +612,19 @@ module subroutine free_open_map( map )
581612
end subroutine free_open_map
582613

583614

615+
module subroutine get_all_open_keys(map, all_keys)
616+
!! Version: Experimental
617+
!!
618+
!! Returns all the keys contained in a hashmap
619+
!! Arguments:
620+
!! map - an open hash map
621+
!! all_keys - all the keys contained in a hash map
622+
!
623+
class(open_hashmap_type), intent(in) :: map
624+
type(key_type), allocatable, intent(out) :: all_keys(:)
625+
end subroutine get_all_open_keys
626+
627+
584628
module subroutine get_other_open_data( map, key, other, exists )
585629
!! Version: Experimental
586630
!!

0 commit comments

Comments
 (0)