Skip to content

Commit

Permalink
added an example for get_all_keys
Browse files Browse the repository at this point in the history
  • Loading branch information
degawa committed Oct 13, 2023
1 parent f7fa292 commit 7cde920
Show file tree
Hide file tree
Showing 2 changed files with 54 additions and 0 deletions.
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
53 changes: 53 additions & 0 deletions example/hashmaps/example_hashmaps_get_all_keys.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,53 @@
program example_set_other_data
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
function key_to_char(key) result(str)
implicit none
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_set_other_data

0 comments on commit 7cde920

Please sign in to comment.