@@ -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,56 @@ 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+ return
209+ else
210+ call map%map_entry(key)
211+ end if
212+ end do
213+
214+ ! Count number of keys that occur an odd number of times
215+ allocate(key_counts(minval(keys):maxval(keys)), source = 0)
216+ do n = 1, n_max
217+ key_counts(keys(n)) = key_counts(keys(n)) + 1
218+ end do
219+ n = sum(iand(key_counts, 1))
220+
221+ call check(error, map%entries(), n, &
222+ "chaining-removal-spec: Number of expected keys and entries are different.")
223+ return
224+
225+ end subroutine
226+
176227end module
177228
178229module test_stdlib_open_maps
@@ -215,6 +266,7 @@ contains
215266 , new_unittest("open-maps-${hash_}$-${size_}$-byte-words", test_${hash_}$_${size_}$_byte_words) &
216267 #:endfor
217268 #:endfor
269+ , new_unittest("open-maps-removal-spec", test_removal_spec) &
218270 ]
219271
220272 end subroutine collect_stdlib_open_maps
@@ -347,6 +399,56 @@ contains
347399
348400 end subroutine
349401
402+ subroutine test_removal_spec(error)
403+ !! Test following code provided by @jannisteunissen
404+ !! https://github.com/fortran-lang/stdlib/issues/785
405+ type(error_type), allocatable, intent(out) :: error
406+
407+ type(open_hashmap_type) :: map
408+ type(key_type) :: key
409+ integer, parameter :: n_max = 500
410+ integer :: n
411+ integer, allocatable :: key_counts(:)
412+ integer, allocatable :: seed(:)
413+ integer(int8) :: int32_int8(4)
414+ integer(int32) :: keys(n_max)
415+ real(dp) :: r_uniform(n_max)
416+ logical :: existed, present
417+
418+ call random_seed(size = n)
419+ allocate(seed(n), source = 123456)
420+ call random_seed(put = seed)
421+
422+ call random_number(r_uniform)
423+ keys = nint(r_uniform * n_max * 0.25_dp)
424+
425+ call map%init(fnv_1_hasher, slots_bits=10)
426+
427+ do n = 1, n_max
428+ call set(key, transfer(keys(n), int32_int8))
429+ call map%key_test(key, present)
430+ if (present) then
431+ call map%remove(key, existed)
432+ call check(error, existed, "open-removal-spec: Key not found in entry removal.")
433+ return
434+ else
435+ call map%map_entry(key)
436+ end if
437+ end do
438+
439+ ! Count number of keys that occur an odd number of times
440+ allocate(key_counts(minval(keys):maxval(keys)), source = 0)
441+ do n = 1, n_max
442+ key_counts(keys(n)) = key_counts(keys(n)) + 1
443+ end do
444+ n = sum(iand(key_counts, 1))
445+
446+ call check(error, map%entries(), n, &
447+ "open-removal-spec: Number of expected keys and entries are different.")
448+ return
449+
450+ end subroutine
451+
350452end module
351453
352454
0 commit comments