Skip to content

Commit

Permalink
Merge branch 'master' of https://github.com/jalvesz/stdlib
Browse files Browse the repository at this point in the history
  • Loading branch information
jalvesz committed Oct 31, 2023
2 parents c0f38d4 + b8fbb3c commit f0b80ae
Show file tree
Hide file tree
Showing 8 changed files with 287 additions and 2 deletions.
48 changes: 46 additions & 2 deletions doc/specs/stdlib_hashmaps.md
Original file line number Diff line number Diff line change
Expand Up @@ -890,7 +890,10 @@ It also defines five non-overridable procedures:
* `num_slots` - returns the number of slots in the map; and

* `slots_bits` - returns the number of bits used to address the slots;
and eleven deferred procedures:

and ten deferred procedures:

* `get_all_keys` - gets all the keys contained in a map;

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

Expand Down Expand Up @@ -932,6 +935,7 @@ The type's definition is below:
procedure, non_overridable, pass(map) :: map_probes
procedure, non_overridable, pass(map) :: slots_bits
procedure, non_overridable, pass(map) :: num_slots
procedure(get_all_keys), deferred, pass(map) :: get_all_keys
procedure(get_other), deferred, pass(map) :: get_other_data
procedure(init_map), deferred, pass(map) :: init
procedure(key_test), deferred, pass(map) :: key_test
Expand Down Expand Up @@ -1026,6 +1030,7 @@ as follows:
type(chaining_map_entry_ptr), allocatable :: inverse(:)
type(chaining_map_entry_ptr), allocatable :: slots(:)
contains
procedure :: get_all_keys => get_all_chaining_keys
procedure :: get_other_data => get_other_chaining_data
procedure :: init => init_chaining_map
procedure :: key => chaining_key_test
Expand Down Expand Up @@ -1103,6 +1108,7 @@ as follows:
type(open_map_entry_ptr), allocatable :: inverse(:)
integer(int_index), allocatable :: slots(:)
contains
procedure :: get_all_keys => get_all_open_keys
procedure :: get_other_data => get_other_open_data
procedure :: init => init_open_map
procedure :: key_test => open_key_test
Expand Down Expand Up @@ -1148,6 +1154,9 @@ Procedures to modify the content of a map:

Procedures to report the content of a map:

* `map % get_all_keys( all_keys )` - Returns all the keys
contained in the map;

* `map % get_other_data( key, other, exists )` - Returns the other data
associated with the `key`;

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


#### `get_all_keys` - Returns all the keys contained in a map

##### Status

Experimental

##### Description

Returns all the keys contained in a map.

##### Syntax

`call map % [[hashmap_type(type):get_all_keys(bound)]]( all_keys )`

##### Class

Subroutine

##### Arguments

`map` (pass): shall be a scalar variable of class
`chaining_hashmap_type` or `open_hashmap_type`. It is an
`intent(in)` argument. It will be
the hash map used to store and access the other data.

`all_keys`: shall be a rank-1 allocatable array of type `key_type`.
It is an `intent(out)` argument.

##### Example

```fortran
{!example/hashmaps/example_hashmaps_get_all_keys.f90!}
```


#### `get_other_data` - Returns other data associated with the `key`

##### Status
Expand Down Expand Up @@ -1478,7 +1522,7 @@ entry.
associated with the `key`.

`conflict` (optional): shall be a scalar variable of type
`logical`. It is an `intent(in)` argument. If present, a `.true.`
`logical`. It is an `intent(out)` argument. If present, a `.true.`
value indicates that an entry with the value of `key` already exists
and the entry was not entered into the map, a `.false.` value indicates
that `key` was not present in the map and the entry was added to the
Expand Down
1 change: 1 addition & 0 deletions example/hashmaps/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ ADD_EXAMPLE(hashmaps_fnv_1_hasher)
ADD_EXAMPLE(hashmaps_free_key)
ADD_EXAMPLE(hashmaps_free_other)
ADD_EXAMPLE(hashmaps_get)
ADD_EXAMPLE(hashmaps_get_all_keys)
ADD_EXAMPLE(hashmaps_get_other_data)
ADD_EXAMPLE(hashmaps_hasher_fun)
ADD_EXAMPLE(hashmaps_init)
Expand Down
52 changes: 52 additions & 0 deletions example/hashmaps/example_hashmaps_get_all_keys.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,52 @@
program example_hashmaps_get_all_keys
use stdlib_kinds, only: int32
use stdlib_hashmaps, only: chaining_hashmap_type
use stdlib_hashmap_wrappers, only: fnv_1_hasher, &
key_type, other_type, set
implicit none
type(chaining_hashmap_type) :: map
type(key_type) :: key
type(other_type) :: other

type(key_type), allocatable :: keys(:)
integer(int32) :: i

call map%init(fnv_1_hasher)

! adding key-value pairs to the map
call set(key, "initial key")
call set(other, "value 1")
call map%map_entry(key, other)

call set(key, "second key")
call set(other, "value 2")
call map%map_entry(key, other)

call set(key, "last key")
call set(other, "value 3")
call map%map_entry(key, other)

! getting all the keys in the map
call map%get_all_keys(keys)

print '("Number of keys in the hashmap = ", I0)', size(keys)
!Number of keys in the hashmap = 3

do i = 1, size(keys)
print '("Value of key ", I0, " = ", A)', i, key_to_char(keys(i))
end do
!Value of key 1 = initial key
!Value of key 2 = second key
!Value of key 3 = last key

contains
!Converts key type to character type
pure function key_to_char(key) result(str)
type(key_type), intent(in) :: key
character(:), allocatable :: str
character(:), allocatable :: str_mold

allocate( character(len=size(key%value)) :: str_mold )
str = transfer(key%value, str_mold)
end function key_to_char
end program example_hashmaps_get_all_keys
31 changes: 31 additions & 0 deletions src/stdlib_hashmap_chaining.f90
Original file line number Diff line number Diff line change
Expand Up @@ -284,6 +284,37 @@ recursive subroutine free_map_entry_pool(pool) ! gent_pool_free
end subroutine free_map_entry_pool


module subroutine get_all_chaining_keys(map, all_keys)
!! Version: Experimental
!!
!! Returns all the keys contained in a hash map
!! Arguments:
!! map - a chaining hash map
!! all_keys - all the keys contained in a hash map
!
class(chaining_hashmap_type), intent(in) :: map
type(key_type), allocatable, intent(out) :: all_keys(:)

integer(int32) :: num_keys
integer(int_index) :: i, key_idx

num_keys = map % entries()
allocate( all_keys(num_keys) )
if ( num_keys == 0 ) return

if( allocated( map % inverse ) ) then
key_idx = 1_int_index
do i=1_int_index, size( map % inverse, kind=int_index )
if ( associated( map % inverse(i) % target ) ) then
all_keys(key_idx) = map % inverse(i) % target % key
key_idx = key_idx + 1_int_index
end if
end do
end if

end subroutine get_all_chaining_keys


module subroutine get_other_chaining_data( map, key, other, exists )
!! Version: Experimental
!!
Expand Down
31 changes: 31 additions & 0 deletions src/stdlib_hashmap_open.f90
Original file line number Diff line number Diff line change
Expand Up @@ -254,6 +254,37 @@ module subroutine free_open_map( map )
end subroutine free_open_map


module subroutine get_all_open_keys(map, all_keys)
!! Version: Experimental
!!
!! Returns all the keys contained in a hash map
!! Arguments:
!! map - an open hash map
!! all_keys - all the keys contained in a hash map
!
class(open_hashmap_type), intent(in) :: map
type(key_type), allocatable, intent(out) :: all_keys(:)

integer(int32) :: num_keys
integer(int_index) :: i, key_idx

num_keys = map % entries()
allocate( all_keys(num_keys) )
if ( num_keys == 0 ) return

if ( allocated( map % inverse) ) then
key_idx = 1_int_index
do i=1_int_index, size( map % inverse, kind=int_index )
if ( associated( map % inverse(i) % target ) ) then
all_keys(key_idx) = map % inverse(i) % target % key
key_idx = key_idx + 1_int_index
end if
end do
end if

end subroutine get_all_open_keys


module subroutine get_other_open_data( map, key, other, exists )
!! Version: Experimental
!!
Expand Down
44 changes: 44 additions & 0 deletions src/stdlib_hashmaps.f90
Original file line number Diff line number Diff line change
Expand Up @@ -94,6 +94,7 @@ module stdlib_hashmaps
procedure, non_overridable, pass(map) :: map_probes
procedure, non_overridable, pass(map) :: num_slots
procedure, non_overridable, pass(map) :: slots_bits
procedure(get_all_keys), deferred, pass(map) :: get_all_keys
procedure(get_other), deferred, pass(map) :: get_other_data
procedure(init_map), deferred, pass(map) :: init
procedure(key_test), deferred, pass(map) :: key_test
Expand All @@ -109,6 +110,21 @@ module stdlib_hashmaps

abstract interface

subroutine get_all_keys(map, all_keys)
!! Version: Experimental
!!
!! Returns the all keys contained in a hash map
!! ([Specifications](../page/specs/stdlib_hashmaps.html#get_all_keys-returns-all-the-keys-contained-in-a-map))
!!
!! Arguments:
!! map - a hash map
!! all_keys - all the keys contained in a hash map
!
import hashmap_type, key_type
class(hashmap_type), intent(in) :: map
type(key_type), allocatable, intent(out) :: all_keys(:)
end subroutine get_all_keys

subroutine get_other( map, key, other, exists )
!! Version: Experimental
!!
Expand Down Expand Up @@ -319,6 +335,7 @@ end function total_depth
type(chaining_map_entry_ptr), allocatable :: slots(:)
!! Array of bucket lists Note # slots=size(slots)
contains
procedure :: get_all_keys => get_all_chaining_keys
procedure :: get_other_data => get_other_chaining_data
procedure :: init => init_chaining_map
procedure :: loading => chaining_loading
Expand All @@ -345,6 +362,19 @@ module subroutine free_chaining_map( map )
end subroutine free_chaining_map


module subroutine get_all_chaining_keys(map, all_keys)
!! Version: Experimental
!!
!! Returns all the keys contained in a hashmap
!! Arguments:
!! map - an chaining hash map
!! all_keys - all the keys contained in a hash map
!
class(chaining_hashmap_type), intent(in) :: map
type(key_type), allocatable, intent(out) :: all_keys(:)
end subroutine get_all_chaining_keys


module subroutine get_other_chaining_data( map, key, other, exists )
!! Version: Experimental
!!
Expand Down Expand Up @@ -556,6 +586,7 @@ end function total_chaining_depth
integer(int_index), allocatable :: slots(:)
!! Array of indices to the inverse Note # slots=size(slots)
contains
procedure :: get_all_keys => get_all_open_keys
procedure :: get_other_data => get_other_open_data
procedure :: init => init_open_map
procedure :: loading => open_loading
Expand All @@ -581,6 +612,19 @@ module subroutine free_open_map( map )
end subroutine free_open_map


module subroutine get_all_open_keys(map, all_keys)
!! Version: Experimental
!!
!! Returns all the keys contained in a hashmap
!! Arguments:
!! map - an open hash map
!! all_keys - all the keys contained in a hash map
!
class(open_hashmap_type), intent(in) :: map
type(key_type), allocatable, intent(out) :: all_keys(:)
end subroutine get_all_open_keys


module subroutine get_other_open_data( map, key, other, exists )
!! Version: Experimental
!!
Expand Down
Loading

0 comments on commit f0b80ae

Please sign in to comment.