diff --git a/doc/specs/stdlib_hashmaps.md b/doc/specs/stdlib_hashmaps.md index 0fa8332fb..ea541d780 100644 --- a/doc/specs/stdlib_hashmaps.md +++ b/doc/specs/stdlib_hashmaps.md @@ -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; @@ -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 @@ -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 @@ -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 @@ -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`; @@ -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 diff --git a/example/hashmaps/CMakeLists.txt b/example/hashmaps/CMakeLists.txt index c3962fcfb..fa97acd0a 100644 --- a/example/hashmaps/CMakeLists.txt +++ b/example/hashmaps/CMakeLists.txt @@ -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) diff --git a/example/hashmaps/example_hashmaps_get_all_keys.f90 b/example/hashmaps/example_hashmaps_get_all_keys.f90 new file mode 100644 index 000000000..2188fb181 --- /dev/null +++ b/example/hashmaps/example_hashmaps_get_all_keys.f90 @@ -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 diff --git a/src/stdlib_hashmap_chaining.f90 b/src/stdlib_hashmap_chaining.f90 index 7db08861a..273545680 100755 --- a/src/stdlib_hashmap_chaining.f90 +++ b/src/stdlib_hashmap_chaining.f90 @@ -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 !! diff --git a/src/stdlib_hashmap_open.f90 b/src/stdlib_hashmap_open.f90 index 979b097e9..b271f9869 100755 --- a/src/stdlib_hashmap_open.f90 +++ b/src/stdlib_hashmap_open.f90 @@ -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 !! diff --git a/src/stdlib_hashmaps.f90 b/src/stdlib_hashmaps.f90 index f7f29c683..4b3044583 100644 --- a/src/stdlib_hashmaps.f90 +++ b/src/stdlib_hashmaps.f90 @@ -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 @@ -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 !! @@ -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 @@ -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 !! @@ -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 @@ -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 !! diff --git a/test/hashmaps/test_chaining_maps.f90 b/test/hashmaps/test_chaining_maps.f90 index d63346e3d..13d062118 100755 --- a/test/hashmaps/test_chaining_maps.f90 +++ b/test/hashmaps/test_chaining_maps.f90 @@ -51,6 +51,7 @@ program test_chaining_maps call map % init( fnv_1_hasher, slots_bits=10 ) call input_random_data( map, test_16, 'FNV-1', "16 byte words" ) call test_inquire_data( map, test_16, 'FNV-1', "16 byte words" ) + call test_get_all_keys( map, test_16, 'FNV-1', '16 byte words' ) call test_get_data( map, test_16, 'FNV-1', '16 byte words' ) call report_rehash_times( map, fnv_1_hasher, 'FNV-1', '16 byte words' ) call report_hash_statistics( map, 'FNV-1', '16 byte words' ) @@ -60,6 +61,7 @@ program test_chaining_maps call input_random_data( map, test_256, 'FNV-1', "256 byte words" ) call test_inquire_data( map, test_256, 'FNV-1', "256 byte words" ) call test_get_data( map, test_256, 'FNV-1', '256 byte words' ) + call test_get_all_keys( map, test_256, 'FNV-1', '256 byte words' ) call report_rehash_times( map, fnv_1_hasher, 'FNV-1', '256 byte words' ) call report_hash_statistics( map, 'FNV-1', '256 byte words' ) call report_removal_times( map, test_256, 'FNV-1', '256 byte words' ) @@ -68,6 +70,7 @@ program test_chaining_maps call input_random_data( map, test_16, 'FNV-1A', "16 byte words" ) call test_inquire_data( map, test_16, 'FNV-1A', "16 byte words" ) call test_get_data( map, test_16, 'FNV-1A', '16 byte words' ) + call test_get_all_keys( map, test_16, 'FNV-1A', '16 byte words' ) call report_rehash_times( map, fnv_1a_hasher, 'FNV-1', '16 byte words' ) call report_hash_statistics( map, 'FNV-1A', '16 byte words' ) call report_removal_times( map, test_16, 'FNV-1a', '16 byte words' ) @@ -76,6 +79,7 @@ program test_chaining_maps call input_random_data( map, test_256, 'FNV-1A', "256 byte words" ) call test_inquire_data( map, test_256, 'FNV-1A', "256 byte words" ) call test_get_data( map, test_256, 'FNV-1A', '256 byte words' ) + call test_get_all_keys( map, test_256, 'FNV-1A', '256 byte words' ) call report_rehash_times( map, fnv_1_hasher, 'FNV-1A', '256 byte words' ) call report_hash_statistics( map, 'FNV-1A', '256 byte words' ) call report_removal_times( map, test_256, 'FNV-1A', '256 byte words' ) @@ -84,6 +88,7 @@ program test_chaining_maps call input_random_data( map, test_16, 'Seeded_Nmhash32', "16 byte words" ) call test_inquire_data( map, test_16, 'Seeded_Nmhash32', "16 byte words" ) call test_get_data( map, test_16, 'Seeded_Nmhash32', '16 byte words' ) + call test_get_all_keys( map, test_16, 'Seeded_Nmhash32', '16 byte words' ) call report_rehash_times( map, seeded_nmhash32_hasher, 'Seeded_Nmhash32', & '16 byte words' ) call report_hash_statistics( map, 'Seeded_Nmhash32', '16 byte words' ) @@ -94,6 +99,7 @@ program test_chaining_maps call input_random_data( map, test_256, 'Seeded_Nmhash32', "256 byte words" ) call test_inquire_data( map, test_256, 'Seeded_Nmhash32', "256 byte words" ) call test_get_data( map, test_256, 'Seeded_Nmhash32', '256 byte words' ) + call test_get_all_keys( map, test_256, 'Seeded_Nmhash32', '256 byte words' ) call report_rehash_times( map, seeded_nmhash32_hasher, 'Seeded_Nmhash32', & '256 byte words' ) call report_hash_statistics( map, 'Seeded_Nmhash32', '256 byte words' ) @@ -104,6 +110,7 @@ program test_chaining_maps call input_random_data( map, test_16, 'Seeded_Nmhash32x', "16 byte words" ) call test_inquire_data( map, test_16, 'Seeded_Nmhash32x', "16 byte words" ) call test_get_data( map, test_16, 'Seeded_Nmhash32x', '16 byte words' ) + call test_get_all_keys( map, test_16, 'Seeded_Nmhash32x', '16 byte words' ) call report_rehash_times( map, seeded_nmhash32x_hasher, & 'Seeded_Nmhash32x', '16 byte words' ) call report_hash_statistics( map, 'Seeded_Nmhash32x', '16 byte words' ) @@ -116,6 +123,7 @@ program test_chaining_maps call test_inquire_data( map, test_256, 'Seeded_Nmhash32x', & "256 byte words" ) call test_get_data( map, test_256, 'Seeded_Nmhash32x', '256 byte words' ) + call test_get_all_keys( map, test_256, 'Seeded_Nmhash32x', '256 byte words' ) call report_rehash_times( map, seeded_nmhash32x_hasher, & 'Seeded_Nmhash32x', '256 byte words' ) call report_hash_statistics( map, 'Seeded_Nmhash32x', '256 byte words' ) @@ -126,6 +134,7 @@ program test_chaining_maps call input_random_data( map, test_16, 'Seeded_Water', "16 byte words" ) call test_inquire_data( map, test_16, 'Seeded_Water', "16 byte words" ) call test_get_data( map, test_16, 'Seeded_Water', '16 byte words' ) + call test_get_all_keys( map, test_16, 'Seeded_Water', '16 byte words' ) call report_rehash_times( map, seeded_water_hasher, & 'Seeded_Water', '16 byte words' ) call report_hash_statistics( map, 'Seeded_Water', '16 byte words' ) @@ -138,6 +147,7 @@ program test_chaining_maps call test_inquire_data( map, test_256, 'Seeded_Water', & "256 byte words" ) call test_get_data( map, test_256, 'Seeded_Water', '256 byte words' ) + call test_get_all_keys( map, test_256, 'Seeded_Water', '256 byte words' ) call report_rehash_times( map, seeded_water_hasher, & 'Seeded_Water', '256 byte words' ) call report_hash_statistics( map, 'Seeded_Water', '256 byte words' ) @@ -227,6 +237,37 @@ subroutine test_get_data( map, test_block, hash_name, size_name ) end subroutine test_get_data + subroutine test_get_all_keys( map, test_block, hash_name, size_name ) + type(chaining_hashmap_type), intent(inout) :: map + integer(int_index), intent(in) :: test_block + character(*), intent(in) :: hash_name, size_name + integer :: index2, key_idx + type(key_type) :: key + type(key_type), allocatable :: all_keys(:) + real :: t1, t2, tdiff + + call cpu_time(t1) + call map % get_all_keys(all_keys) + call cpu_time(t2) + tdiff = t2-t1 + + if (size( all_keys ) /= size( test_8_bits )/test_block) & + error stop "Number of keys is different from that of keys in a map." + + do index2=1, size(test_8_bits), test_block + call set( key, test_8_bits( index2:index2+test_block-1 ) ) + + key_idx = ( index2/test_block ) + 1 + if (.not. ( all_keys(key_idx) == key )) & + error stop "Invalid value of a key." + end do + + write(lun, '("|", a18, " | ", a12, " | ", a15, " | ", f10.5, " |")') & + trim(hash_name), 'Get all keys', size_name, tdiff + + end subroutine test_get_all_keys + + subroutine report_rehash_times( map, hasher, hash_name, size_name ) type(chaining_hashmap_type), intent(inout) :: map procedure(hasher_fun) :: hasher diff --git a/test/hashmaps/test_open_maps.f90 b/test/hashmaps/test_open_maps.f90 index d569d238c..7e1ff9764 100755 --- a/test/hashmaps/test_open_maps.f90 +++ b/test/hashmaps/test_open_maps.f90 @@ -53,6 +53,7 @@ program test_open_maps call input_random_data( map, test_16, 'FNV-1', "16 byte words" ) call test_inquire_data( map, test_16, 'FNV-1', "16 byte words" ) call test_get_data( map, test_16, 'FNV-1', '16 byte words' ) + call test_get_all_keys( map, test_16, 'FNV-1', '16 byte words' ) call report_rehash_times( map, fnv_1_hasher, 'FNV-1', '16 byte words' ) call report_hash_statistics( map, 'FNV-1', '16 byte words' ) call report_removal_times( map, test_16, 'FNV-1', '16 byte words' ) @@ -61,6 +62,7 @@ program test_open_maps call input_random_data( map, test_256, 'FNV-1', "256 byte words" ) call test_inquire_data( map, test_256, 'FNV-1', "256 byte words" ) call test_get_data( map, test_256, 'FNV-1', '256 byte words' ) + call test_get_all_keys( map, test_256, 'FNV-1', '256 byte words' ) call report_rehash_times( map, fnv_1_hasher, 'FNV-1', '256 byte words' ) call report_hash_statistics( map, 'FNV-1', '256 byte words' ) call report_removal_times( map, test_256, 'FNV-1', '256 byte words' ) @@ -69,6 +71,7 @@ program test_open_maps call input_random_data( map, test_16, 'FNV-1A', "16 byte words" ) call test_inquire_data( map, test_16, 'FNV-1A', "16 byte words" ) call test_get_data( map, test_16, 'FNV-1A', '16 byte words' ) + call test_get_all_keys( map, test_16, 'FNV-1A', '16 byte words' ) call report_rehash_times( map, fnv_1a_hasher, 'FNV-1', '16 byte words' ) call report_hash_statistics( map, 'FNV-1A', '16 byte words' ) call report_removal_times( map, test_16, 'FNV-1a', '16 byte words' ) @@ -77,6 +80,7 @@ program test_open_maps call input_random_data( map, test_256, 'FNV-1A', "256 byte words" ) call test_inquire_data( map, test_256, 'FNV-1A', "256 byte words" ) call test_get_data( map, test_256, 'FNV-1A', '256 byte words' ) + call test_get_all_keys( map, test_256, 'FNV-1A', '256 byte words' ) call report_rehash_times( map, fnv_1_hasher, 'FNV-1A', '256 byte words' ) call report_hash_statistics( map, 'FNV-1A', '256 byte words' ) call report_removal_times( map, test_256, 'FNV-1A', '256 byte words' ) @@ -85,6 +89,7 @@ program test_open_maps call input_random_data( map, test_16, 'Seeded_Nmhash32', "16 byte words" ) call test_inquire_data( map, test_16, 'Seeded_Nmhash32', "16 byte words" ) call test_get_data( map, test_16, 'Seeded_Nmhash32', '16 byte words' ) + call test_get_all_keys( map, test_16, 'Seeded_Nmhash32', '16 byte words' ) call report_rehash_times( map, seeded_nmhash32_hasher, 'Seeded_Nmhash32', & '16 byte words' ) call report_hash_statistics( map, 'Seeded_Nmhash32', '16 byte words' ) @@ -95,6 +100,7 @@ program test_open_maps call input_random_data( map, test_256, 'Seeded_Nmhash32', "256 byte words" ) call test_inquire_data( map, test_256, 'Seeded_Nmhash32', "256 byte words" ) call test_get_data( map, test_256, 'Seeded_Nmhash32', '256 byte words' ) + call test_get_all_keys( map, test_256, 'Seeded_Nmhash32', '256 byte words' ) call report_rehash_times( map, seeded_nmhash32_hasher, 'Seeded_Nmhash32', & '256 byte words' ) call report_hash_statistics( map, 'Seeded_Nmhash32', '256 byte words' ) @@ -105,6 +111,7 @@ program test_open_maps call input_random_data( map, test_16, 'Seeded_Nmhash32x', "16 byte words" ) call test_inquire_data( map, test_16, 'Seeded_Nmhash32x', "16 byte words" ) call test_get_data( map, test_16, 'Seeded_Nmhash32x', '16 byte words' ) + call test_get_all_keys( map, test_16, 'Seeded_Nmhash32x', '16 byte words' ) call report_rehash_times( map, seeded_nmhash32x_hasher, & 'Seeded_Nmhash32x', '16 byte words' ) call report_hash_statistics( map, 'Seeded_Nmhash32x', '16 byte words' ) @@ -117,6 +124,7 @@ program test_open_maps call test_inquire_data( map, test_256, 'Seeded_Nmhash32x', & "256 byte words" ) call test_get_data( map, test_256, 'Seeded_Nmhash32x', '256 byte words' ) + call test_get_all_keys( map, test_256, 'Seeded_Nmhash32x', '256 byte words' ) call report_rehash_times( map, seeded_nmhash32x_hasher, & 'Seeded_Nmhash32x', '256 byte words' ) call report_hash_statistics( map, 'Seeded_Nmhash32x', '256 byte words' ) @@ -127,6 +135,7 @@ program test_open_maps call input_random_data( map, test_16, 'Seeded_Water', "16 byte words" ) call test_inquire_data( map, test_16, 'Seeded_Water', "16 byte words" ) call test_get_data( map, test_16, 'Seeded_Water', '16 byte words' ) + call test_get_all_keys( map, test_16, 'Seeded_Water', '16 byte words' ) call report_rehash_times( map, seeded_water_hasher, & 'Seeded_Water', '16 byte words' ) call report_hash_statistics( map, 'Seeded_Water', '16 byte words' ) @@ -139,6 +148,7 @@ program test_open_maps call test_inquire_data( map, test_256, 'Seeded_Water', & "256 byte words" ) call test_get_data( map, test_256, 'Seeded_Water', '256 byte words' ) + call test_get_all_keys( map, test_256, 'Seeded_Water', '256 byte words' ) call report_rehash_times( map, seeded_water_hasher, & 'Seeded_Water', '256 byte words' ) call report_hash_statistics( map, 'Seeded_Water', '256 byte words' ) @@ -228,6 +238,37 @@ subroutine test_get_data( map, test_block, hash_name, size_name ) end subroutine test_get_data + subroutine test_get_all_keys( map, test_block, hash_name, size_name ) + type(open_hashmap_type), intent(inout) :: map + integer(int_index), intent(in) :: test_block + character(*), intent(in) :: hash_name, size_name + integer :: index2, key_idx + type(key_type) :: key + type(key_type), allocatable :: all_keys(:) + real :: t1, t2, tdiff + + call cpu_time(t1) + call map % get_all_keys(all_keys) + call cpu_time(t2) + tdiff = t2-t1 + + if (size( all_keys ) /= size( test_8_bits )/test_block) & + error stop "Number of keys is different from that of keys in a map." + + do index2=1, size(test_8_bits), test_block + call set( key, test_8_bits( index2:index2+test_block-1 ) ) + + key_idx = ( index2/test_block ) + 1 + if (.not. ( all_keys(key_idx) == key )) & + error stop "Invalid value of a key." + end do + + write(lun, '("|", a18, " | ", a12, " | ", a15, " | ", f10.5, " |")') & + trim(hash_name), 'Get all keys', size_name, tdiff + + end subroutine test_get_all_keys + + subroutine report_rehash_times( map, hasher, hash_name, size_name ) type(open_hashmap_type), intent(inout) :: map procedure(hasher_fun) :: hasher