Skip to content

Commit 834d07b

Browse files
committed
Addition of a test for the procedure remove for chaining maps
1 parent df45374 commit 834d07b

File tree

1 file changed

+100
-0
lines changed

1 file changed

+100
-0
lines changed

test/hashmaps/test_maps.fypp

Lines changed: 100 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,7 @@ contains
4141
, new_unittest("chaining-maps-${hash_}$-${size_}$-byte-words", test_${hash_}$_${size_}$_byte_words) &
4242
#:endfor
4343
#:endfor
44+
, new_unittest("chaining-maps-removal-spec", test_removal_spec) &
4445
]
4546

4647
end subroutine collect_stdlib_chaining_maps
@@ -173,6 +174,55 @@ contains
173174

174175
end subroutine
175176

177+
subroutine test_removal_spec(error)
178+
!! Test following code provided by @jannisteunissen
179+
!! https://github.com/fortran-lang/stdlib/issues/785
180+
type(error_type), allocatable, intent(out) :: error
181+
182+
type(chaining_hashmap_type) :: map
183+
type(key_type) :: key
184+
integer, parameter :: n_max = 500
185+
integer :: n
186+
integer, allocatable :: key_counts(:)
187+
integer, allocatable :: seed(:)
188+
integer(int8) :: int32_int8(4)
189+
integer(int32) :: keys(n_max)
190+
real(dp) :: r_uniform(n_max)
191+
logical :: existed, present
192+
193+
call random_seed(size = n)
194+
allocate(seed(n), source = 123456)
195+
call random_seed(put = seed)
196+
197+
call random_number(r_uniform)
198+
keys = nint(r_uniform * n_max * 0.25_dp)
199+
200+
call map%init(fnv_1_hasher, slots_bits=10)
201+
202+
do n = 1, n_max
203+
call set(key, transfer(keys(n), int32_int8))
204+
call map%key_test(key, present)
205+
if (present) then
206+
call map%remove(key, existed)
207+
call check(error, existed, "chaining-removal-spec: Key not found in entry removal.")
208+
else
209+
call map%map_entry(key)
210+
end if
211+
end do
212+
213+
! Count number of keys that occur an odd number of times
214+
allocate(key_counts(minval(keys):maxval(keys)), source = 0)
215+
do n = 1, n_max
216+
key_counts(keys(n)) = key_counts(keys(n)) + 1
217+
end do
218+
n = sum(iand(key_counts, 1))
219+
220+
call check(error, map%entries(), n, &
221+
"chaining-removal-spec: Number of expected keys and entries are different.")
222+
return
223+
224+
end subroutine
225+
176226
end module
177227

178228
module test_stdlib_open_maps
@@ -215,6 +265,7 @@ contains
215265
, new_unittest("open-maps-${hash_}$-${size_}$-byte-words", test_${hash_}$_${size_}$_byte_words) &
216266
#:endfor
217267
#:endfor
268+
, new_unittest("open-maps-removal-spec", test_removal_spec) &
218269
]
219270

220271
end subroutine collect_stdlib_open_maps
@@ -347,6 +398,55 @@ contains
347398

348399
end subroutine
349400

401+
subroutine test_removal_spec(error)
402+
!! Test following code provided by @jannisteunissen
403+
!! https://github.com/fortran-lang/stdlib/issues/785
404+
type(error_type), allocatable, intent(out) :: error
405+
406+
type(open_hashmap_type) :: map
407+
type(key_type) :: key
408+
integer, parameter :: n_max = 500
409+
integer :: n
410+
integer, allocatable :: key_counts(:)
411+
integer, allocatable :: seed(:)
412+
integer(int8) :: int32_int8(4)
413+
integer(int32) :: keys(n_max)
414+
real(dp) :: r_uniform(n_max)
415+
logical :: existed, present
416+
417+
call random_seed(size = n)
418+
allocate(seed(n), source = 123456)
419+
call random_seed(put = seed)
420+
421+
call random_number(r_uniform)
422+
keys = nint(r_uniform * n_max * 0.25_dp)
423+
424+
call map%init(fnv_1_hasher, slots_bits=10)
425+
426+
do n = 1, n_max
427+
call set(key, transfer(keys(n), int32_int8))
428+
call map%key_test(key, present)
429+
if (present) then
430+
call map%remove(key, existed)
431+
call check(error, existed, "open-removal-spec: Key not found in entry removal.")
432+
else
433+
call map%map_entry(key)
434+
end if
435+
end do
436+
437+
! Count number of keys that occur an odd number of times
438+
allocate(key_counts(minval(keys):maxval(keys)), source = 0)
439+
do n = 1, n_max
440+
key_counts(keys(n)) = key_counts(keys(n)) + 1
441+
end do
442+
n = sum(iand(key_counts, 1))
443+
444+
call check(error, map%entries(), n, &
445+
"open-removal-spec: Number of expected keys and entries are different.")
446+
return
447+
448+
end subroutine
449+
350450
end module
351451

352452

0 commit comments

Comments
 (0)