Skip to content

Commit e911a70

Browse files
committed
added implementaion of get_all_chaining_keys
1 parent 7396f0f commit e911a70

File tree

1 file changed

+31
-0
lines changed

1 file changed

+31
-0
lines changed

src/stdlib_hashmap_chaining.f90

Lines changed: 31 additions & 0 deletions
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 presented in a hash map
291+
!! Arguments:
292+
!! map - a chaining hash map
293+
!! all_keys - all the keys presented 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
!!

0 commit comments

Comments
 (0)