From 65bdc89246f452c819a4f2b2e7dbcf280da2bff4 Mon Sep 17 00:00:00 2001 From: chuckyvt <138633930+chuckyvt@users.noreply.github.com> Date: Tue, 26 Mar 2024 22:21:10 -0400 Subject: [PATCH 01/12] Update to include int32 hashmap keytype Update to stdlib_hashmap_wrappers.f90 that includes support for int32 vector key types. --- src/stdlib_hashmap_wrappers.f90 | 18 +++++++++++++++++- 1 file changed, 17 insertions(+), 1 deletion(-) diff --git a/src/stdlib_hashmap_wrappers.f90 b/src/stdlib_hashmap_wrappers.f90 index a2a8b93d2..a582a76d8 100644 --- a/src/stdlib_hashmap_wrappers.f90 +++ b/src/stdlib_hashmap_wrappers.f90 @@ -101,7 +101,8 @@ end function hasher_fun module procedure set_char_key, & set_int8_key, & - set_other + set_other, & + set_int32_key end interface set @@ -308,6 +309,21 @@ subroutine set_other( other, value ) end subroutine set_other + subroutine set_int32_key( key, value ) + !! Version: Experimental + !! + !! Sets the contents of the key from an INTEGER(INT8) vector + !! Arguments: + !! key - the output key + !! value - the input INTEGER(INT32) vector + type(key_type), intent(out) :: key + integer(int32), intent(in) :: value(:) + + key % value = transfer(value, key % value) + + end subroutine set_int32_key + + subroutine set_int8_key( key, value ) !! Version: Experimental !! From 418cb82828e46ba7491e63c14b797690cf3df3b4 Mon Sep 17 00:00:00 2001 From: chuckyvt <138633930+chuckyvt@users.noreply.github.com> Date: Wed, 27 Mar 2024 08:56:06 -0400 Subject: [PATCH 02/12] Update src/stdlib_hashmap_wrappers.f90 Co-authored-by: Jeremie Vandenplas --- src/stdlib_hashmap_wrappers.f90 | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/stdlib_hashmap_wrappers.f90 b/src/stdlib_hashmap_wrappers.f90 index a582a76d8..db54f1724 100644 --- a/src/stdlib_hashmap_wrappers.f90 +++ b/src/stdlib_hashmap_wrappers.f90 @@ -101,8 +101,8 @@ end function hasher_fun module procedure set_char_key, & set_int8_key, & - set_other, & - set_int32_key + set_int32_key, & + set_other end interface set From 561cee22be67e8a2240a6bf486beef74e24d794c Mon Sep 17 00:00:00 2001 From: chuckyvt <138633930+chuckyvt@users.noreply.github.com> Date: Fri, 29 Mar 2024 23:07:36 -0400 Subject: [PATCH 03/12] Update stdlib_hashmap_wrappers.f90 Added get_inte32_key function. --- src/stdlib_hashmap_wrappers.f90 | 46 ++++++++++++++++++++++----------- 1 file changed, 31 insertions(+), 15 deletions(-) diff --git a/src/stdlib_hashmap_wrappers.f90 b/src/stdlib_hashmap_wrappers.f90 index db54f1724..caf23c022 100644 --- a/src/stdlib_hashmap_wrappers.f90 +++ b/src/stdlib_hashmap_wrappers.f90 @@ -88,6 +88,7 @@ end function hasher_fun module procedure get_char_key, & get_int8_key, & + get_int32_key, & get_other end interface get @@ -278,6 +279,21 @@ subroutine get_int8_key( key, value ) end subroutine get_int8_key + subroutine get_int32_key( key, value ) +!! Version: Experimental +!! +!! Gets the contents of the key as an INTEGER(INT8) vector +!! Arguments: +!! key - the input key +!! value - the contents of key mapped to an INTEGER(INT32) vector + type(key_type), intent(in) :: key + integer(int32), allocatable, intent(out) :: value(:) + + value = transfer( key % value, value ) + + end subroutine get_int8_key + + subroutine set_char_key( key, value ) !! Version: Experimental !! @@ -309,21 +325,6 @@ subroutine set_other( other, value ) end subroutine set_other - subroutine set_int32_key( key, value ) - !! Version: Experimental - !! - !! Sets the contents of the key from an INTEGER(INT8) vector - !! Arguments: - !! key - the output key - !! value - the input INTEGER(INT32) vector - type(key_type), intent(out) :: key - integer(int32), intent(in) :: value(:) - - key % value = transfer(value, key % value) - - end subroutine set_int32_key - - subroutine set_int8_key( key, value ) !! Version: Experimental !! @@ -339,6 +340,21 @@ subroutine set_int8_key( key, value ) end subroutine set_int8_key + subroutine set_int32_key( key, value ) +!! Version: Experimental +!! +!! Sets the contents of the key from an INTEGER(INT8) vector +!! Arguments: +!! key - the output key +!! value - the input INTEGER(INT32) vector + type(key_type), intent(out) :: key + integer(int32), intent(in) :: value(:) + + key % value = transfer(value, key % value) + + end subroutine set_int32_key + + pure function fnv_1_hasher( key ) !! Version: Experimental !! From f10f1b79da25f238baa6d11f0349f19dc56af661 Mon Sep 17 00:00:00 2001 From: chuckyvt <138633930+chuckyvt@users.noreply.github.com> Date: Sat, 30 Mar 2024 09:19:16 -0400 Subject: [PATCH 04/12] Bug fix Fixed end subroutine bug --- src/stdlib_hashmap_wrappers.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/stdlib_hashmap_wrappers.f90 b/src/stdlib_hashmap_wrappers.f90 index caf23c022..0f6ea5445 100644 --- a/src/stdlib_hashmap_wrappers.f90 +++ b/src/stdlib_hashmap_wrappers.f90 @@ -291,7 +291,7 @@ subroutine get_int32_key( key, value ) value = transfer( key % value, value ) - end subroutine get_int8_key + end subroutine get_int32_key subroutine set_char_key( key, value ) From 7cf7352514e8b8ebe390a0532cfd4517bc4e7fa0 Mon Sep 17 00:00:00 2001 From: chuckyvt <138633930+chuckyvt@users.noreply.github.com> Date: Wed, 3 Apr 2024 19:59:15 -0400 Subject: [PATCH 05/12] Minor comment cleanup Minor comment cleanup --- src/stdlib_hashmap_wrappers.f90 | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/stdlib_hashmap_wrappers.f90 b/src/stdlib_hashmap_wrappers.f90 index 0f6ea5445..2a19569b4 100644 --- a/src/stdlib_hashmap_wrappers.f90 +++ b/src/stdlib_hashmap_wrappers.f90 @@ -282,7 +282,7 @@ end subroutine get_int8_key subroutine get_int32_key( key, value ) !! Version: Experimental !! -!! Gets the contents of the key as an INTEGER(INT8) vector +!! Gets the contents of the key as an INTEGER(INT32) vector !! Arguments: !! key - the input key !! value - the contents of key mapped to an INTEGER(INT32) vector @@ -343,7 +343,7 @@ end subroutine set_int8_key subroutine set_int32_key( key, value ) !! Version: Experimental !! -!! Sets the contents of the key from an INTEGER(INT8) vector +!! Sets the contents of the key from an INTEGER(INT32) vector !! Arguments: !! key - the output key !! value - the input INTEGER(INT32) vector From 35ed8262715764d4424f6d56acd1518afcba2b92 Mon Sep 17 00:00:00 2001 From: chuckyvt <138633930+chuckyvt@users.noreply.github.com> Date: Wed, 3 Apr 2024 21:31:35 -0400 Subject: [PATCH 06/12] Update stdlib_hashmaps.md Update to include native support for int32 key types. --- doc/specs/stdlib_hashmaps.md | 21 ++++++++++++--------- 1 file changed, 12 insertions(+), 9 deletions(-) diff --git a/doc/specs/stdlib_hashmaps.md b/doc/specs/stdlib_hashmaps.md index ea541d780..a61ab03c3 100644 --- a/doc/specs/stdlib_hashmaps.md +++ b/doc/specs/stdlib_hashmaps.md @@ -157,11 +157,13 @@ Procedures to manipulate `key_type` data: `key_in`, to contents of the key, `key_out`. * `get( key, value )` - extracts the contents of `key` into `value`, - an `int8` array or character string. + an `int8` array, 'int32' array, or character string. * `free_key( key )` - frees the memory in `key`. -* `set( key, value )` - sets the content of `key` to `value`. +* `set( key, value )` - sets the content of `key` to `value`. + Supported key types are `int8` array, `int32` array, and character + string. Procedures to manipulate `other_type` data: @@ -474,9 +476,9 @@ is an `intent(in)` argument. `value`: if the the first argument is of `key_type` `value` shall be an allocatable default character string variable, or -an allocatable vector variable of type integer and kind `int8`, -otherwise the first argument is of `other_type` and `value` shall be -an allocatable of `class(*)`. It is an `intent(out)` argument. +an allocatable vector variable of type integer and kind `int8` or +`int32`, otherwise the first argument is of `other_type` and `value` +shall be an allocatable of `class(*)`. It is an `intent(out)` argument. ##### Example @@ -751,13 +753,14 @@ is an `intent(out)` argument. `value`: if the first argument is `key` `value` shall be a default character string scalar expression, or a vector expression of type integer -and kind `int8`, while for a first argument of type `other` `value` -shall be of type `class(*)`. It is an `intent(in)` argument. +and kind `int8` or `int32`, while for a first argument of type +`other` `value` shall be of type `class(*)`. It is an `intent(in)` +argument. ##### Note -Values of types other than a scalar default character or an -`int8` vector can be used as the basis of a `key` by transferring the +Values of types other than a scalar default character or and +`int8` or `int32` vector can be used as the basis of a `key` by transferring the value to an `int8` vector. ##### Example From cb53f857b54a4a08842a92890648312fc8b9d1ff Mon Sep 17 00:00:00 2001 From: chuckyvt <138633930+chuckyvt@users.noreply.github.com> Date: Sat, 13 Apr 2024 16:45:20 -0400 Subject: [PATCH 07/12] Add character and int32 keytype tests --- test/hashmaps/test_maps.fypp | 195 +++++++++++++++++++++++++---------- 1 file changed, 140 insertions(+), 55 deletions(-) diff --git a/test/hashmaps/test_maps.fypp b/test/hashmaps/test_maps.fypp index 835bb9369..75dc16f23 100644 --- a/test/hashmaps/test_maps.fypp +++ b/test/hashmaps/test_maps.fypp @@ -24,7 +24,8 @@ module test_stdlib_chaining_maps integer, parameter :: test_size = rand_size*4 integer, parameter :: test_16 = 2**4 integer, parameter :: test_256 = 2**8 - + integer, parameter :: key_types = 3 + character(len=*), parameter :: char_type = ' ' public :: collect_stdlib_chaining_maps contains @@ -53,10 +54,10 @@ contains type(error_type), allocatable, intent(out) :: error type(chaining_hashmap_type) :: map - integer(int8) :: test_8_bits(test_size) + integer(int8) :: test_8_bits(test_size,key_types) call generate_vector(test_8_bits) - + call map % init( ${hash_}$, slots_bits=10 ) call test_input_random_data(error, map, test_8_bits, test_${size_}$) @@ -77,29 +78,32 @@ contains subroutine generate_vector(test_8_bits) - integer(int8), intent(out) :: test_8_bits(test_size) + integer(int8), intent(out) :: test_8_bits(test_size, key_types) - integer :: index + integer :: index, key_type real(dp) :: rand2(2) integer(int32) :: rand_object(rand_size) - - do index=1, rand_size - call random_number(rand2) - if (rand2(1) < 0.5_dp) then - rand_object(index) = ceiling(-rand2(2)*hugep1, int32) - 1 - else - rand_object(index) = floor(rand2(2)*hugep1, int32) - end if + integer :: key_type + + do key_type = 1, key_types + do index=1, rand_size + call random_number(rand2) + if (rand2(1) < 0.5_dp) then + rand_object(index) = ceiling(-rand2(2)*hugep1, int32) - 1 + else + rand_object(index) = floor(rand2(2)*hugep1, int32) + end if + end do + + test_8_bits(:,key_type) = transfer( rand_object, 0_int8, test_size ) end do - test_8_bits(:) = transfer( rand_object, 0_int8, test_size ) - end subroutine subroutine test_input_random_data(error, map, test_8_bits, test_block) type(error_type), allocatable, intent(out) :: error type(chaining_hashmap_type), intent(inout) :: map - integer(int8), intent(in) :: test_8_bits(test_size) + integer(int8), intent(in) :: test_8_bits(test_size, key_types) integer(int_index), intent(in) :: test_block class(*), allocatable :: dummy type(dummy_type) :: dummy_val @@ -108,15 +112,28 @@ contains type(other_type) :: other logical :: conflict - do index2=1, size(test_8_bits), test_block - call set( key, test_8_bits( index2:index2+test_block-1 ) ) + do index2=1, test_size, test_block + if (allocated(dummy)) deallocate(dummy) - dummy_val % value = test_8_bits( index2:index2+test_block-1 ) + dummy_val % value = test_8_bits( index2:index2+test_block-1, 1 ) allocate( dummy, source=dummy_val ) call set ( other, dummy ) + + ! Test all key interfaces + call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) + call map % map_entry( key, other, conflict ) + call check(error, .not.conflict, "Unable to map entry because of a key conflict.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) call map % map_entry( key, other, conflict ) call check(error, .not.conflict, "Unable to map entry because of a key conflict.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) + call map % map_entry( key, other, conflict ) + call check(error, .not.conflict, "Unable to map entry because of a key conflict.") + if (allocated(error)) return + end do end subroutine @@ -124,16 +141,25 @@ contains subroutine test_inquire_data(error, map, test_8_bits, test_block) type(error_type), allocatable, intent(out) :: error type(chaining_hashmap_type), intent(inout) :: map - integer(int8), intent(in) :: test_8_bits(test_size) + integer(int8), intent(in) :: test_8_bits(test_size, key_types) integer(int_index), intent(in) :: test_block integer :: index2 logical :: present type(key_type) :: key - do index2=1, size(test_8_bits), test_block - call set( key, test_8_bits( index2:index2+test_block-1 ) ) + do index2=1, test_size, test_block + call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) + call map % key_test( key, present ) + call check(error, present, "KEY not found in map KEY_TEST.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call map % key_test( key, present ) + call check(error, present, "KEY not found in map KEY_TEST.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) call map % key_test( key, present ) call check(error, present, "KEY not found in map KEY_TEST.") + if (allocated(error)) return end do @@ -142,15 +168,23 @@ contains subroutine test_get_data(error, map, test_8_bits, test_block) type(error_type), allocatable, intent(out) :: error type(chaining_hashmap_type), intent(inout) :: map - integer(int8), intent(in) :: test_8_bits(test_size) + integer(int8), intent(in) :: test_8_bits(test_size, key_types) integer(int_index), intent(in) :: test_block integer :: index2 type(key_type) :: key type(other_type) :: other logical :: exists - do index2=1, size(test_8_bits), test_block - call set( key, test_8_bits( index2:index2+test_block-1 ) ) + do index2=1, test_size, test_block + call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) + call map % get_other_data( key, other, exists ) + call check(error, exists, "Unable to get data because key not found in map.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call map % get_other_data( key, other, exists ) + call check(error, exists, "Unable to get data because key not found in map.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) call map % get_other_data( key, other, exists ) call check(error, exists, "Unable to get data because key not found in map.") end do @@ -160,14 +194,22 @@ contains subroutine test_removal(error, map, test_8_bits, test_block) type(error_type), allocatable, intent(out) :: error type(chaining_hashmap_type), intent(inout) :: map - integer(int8), intent(in) :: test_8_bits(test_size) + integer(int8), intent(in) :: test_8_bits(test_size, key_types) integer(int_index), intent(in) :: test_block type(key_type) :: key integer(int_index) :: index2 logical :: existed - do index2=1, size(test_8_bits), test_block - call set( key, test_8_bits( index2:index2+test_block-1 ) ) + do index2=1, test_size, test_block + call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) + call map % remove(key, existed) + call check(error, existed, "Key not found in entry removal.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call map % remove(key, existed) + call check(error, existed, "Key not found in entry removal.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) call map % remove(key, existed) call check(error, existed, "Key not found in entry removal.") end do @@ -249,6 +291,7 @@ module test_stdlib_open_maps integer, parameter :: test_size = rand_size*4 integer, parameter :: test_16 = 2**4 integer, parameter :: test_256 = 2**8 + integer, parameter :: key_types = 3 public :: collect_stdlib_open_maps @@ -278,7 +321,7 @@ contains type(error_type), allocatable, intent(out) :: error type(open_hashmap_type) :: map - integer(int8) :: test_8_bits(test_size) + integer(int8) :: test_8_bits(test_size,key_types) call generate_vector(test_8_bits) @@ -302,29 +345,31 @@ contains subroutine generate_vector(test_8_bits) - integer(int8), intent(out) :: test_8_bits(test_size) + integer(int8), intent(out) :: test_8_bits(test_size, key_types) - integer :: index + integer :: index, key_type real(dp) :: rand2(2) integer(int32) :: rand_object(rand_size) - - do index=1, rand_size - call random_number(rand2) - if (rand2(1) < 0.5_dp) then - rand_object(index) = ceiling(-rand2(2)*hugep1, int32) - 1 - else - rand_object(index) = floor(rand2(2)*hugep1, int32) - end if - end do - - test_8_bits(:) = transfer( rand_object, 0_int8, test_size ) + + do key_type = 1, key_types + do index=1, rand_size + call random_number(rand2) + if (rand2(1) < 0.5_dp) then + rand_object(index) = ceiling(-rand2(2)*hugep1, int32) - 1 + else + rand_object(index) = floor(rand2(2)*hugep1, int32) + end if + end do + + test_8_bits(:,key_type) = transfer( rand_object, 0_int8, test_size ) + enddo end subroutine subroutine test_input_random_data(error, map, test_8_bits, test_block) type(error_type), allocatable, intent(out) :: error type(open_hashmap_type), intent(inout) :: map - integer(int8), intent(in) :: test_8_bits(test_size) + integer(int8), intent(in) :: test_8_bits(test_size, key_types) integer(int_index), intent(in) :: test_block class(*), allocatable :: dummy type(dummy_type) :: dummy_val @@ -333,15 +378,28 @@ contains type(other_type) :: other logical :: conflict - do index2=1, size(test_8_bits), test_block - call set( key, test_8_bits( index2:index2+test_block-1 ) ) + do index2=1, test_size, test_block + if (allocated(dummy)) deallocate(dummy) - dummy_val % value = test_8_bits( index2:index2+test_block-1 ) + dummy_val % value = test_8_bits( index2:index2+test_block-1, 1 ) allocate( dummy, source=dummy_val ) call set ( other, dummy ) + + ! Test all key interfaces + call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) + call map % map_entry( key, other, conflict ) + call check(error, .not.conflict, "Unable to map entry because of a key conflict.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call map % map_entry( key, other, conflict ) + call check(error, .not.conflict, "Unable to map entry because of a key conflict.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) call map % map_entry( key, other, conflict ) call check(error, .not.conflict, "Unable to map entry because of a key conflict.") + if (allocated(error)) return + end do end subroutine @@ -349,17 +407,28 @@ contains subroutine test_inquire_data(error, map, test_8_bits, test_block) type(error_type), allocatable, intent(out) :: error type(open_hashmap_type), intent(inout) :: map - integer(int8), intent(in) :: test_8_bits(test_size) + integer(int8), intent(in) :: test_8_bits(test_size, key_types) integer(int_index), intent(in) :: test_block integer :: index2 logical :: present type(key_type) :: key - do index2=1, size(test_8_bits), test_block - call set( key, test_8_bits( index2:index2+test_block-1 ) ) + do index2=1, test_size, test_block + + call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) + call map % key_test( key, present ) + call check(error, present, "KEY not found in map KEY_TEST.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) call map % key_test( key, present ) call check(error, present, "KEY not found in map KEY_TEST.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) + call map % key_test( key, present ) + call check(error, present, "KEY not found in map KEY_TEST.") + if (allocated(error)) return + end do end subroutine @@ -367,15 +436,23 @@ contains subroutine test_get_data(error, map, test_8_bits, test_block) type(error_type), allocatable, intent(out) :: error type(open_hashmap_type), intent(inout) :: map - integer(int8), intent(in) :: test_8_bits(test_size) + integer(int8), intent(in) :: test_8_bits(test_size, key_types) integer(int_index), intent(in) :: test_block integer :: index2 type(key_type) :: key type(other_type) :: other logical :: exists - do index2=1, size(test_8_bits), test_block - call set( key, test_8_bits( index2:index2+test_block-1 ) ) + do index2=1, test_size, test_block + call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) + call map % get_other_data( key, other, exists ) + call check(error, exists, "Unable to get data because key not found in map.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call map % get_other_data( key, other, exists ) + call check(error, exists, "Unable to get data because key not found in map.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) call map % get_other_data( key, other, exists ) call check(error, exists, "Unable to get data because key not found in map.") end do @@ -385,14 +462,22 @@ contains subroutine test_removal(error, map, test_8_bits, test_block) type(error_type), allocatable, intent(out) :: error type(open_hashmap_type), intent(inout) :: map - integer(int8), intent(in) :: test_8_bits(test_size) + integer(int8), intent(in) :: test_8_bits(test_size, key_types) integer(int_index), intent(in) :: test_block type(key_type) :: key integer(int_index) :: index2 logical :: existed - do index2=1, size(test_8_bits), test_block - call set( key, test_8_bits( index2:index2+test_block-1 ) ) + do index2=1, test_size, test_block + call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) + call map % remove(key, existed) + call check(error, existed, "Key not found in entry removal.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call map % remove(key, existed) + call check(error, existed, "Key not found in entry removal.") + + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) call map % remove(key, existed) call check(error, existed, "Key not found in entry removal.") end do From fe3fffc8ae2af852b266454f753348519db70806 Mon Sep 17 00:00:00 2001 From: chuckyvt <138633930+chuckyvt@users.noreply.github.com> Date: Sun, 14 Apr 2024 22:01:55 -0400 Subject: [PATCH 08/12] Update test_maps to include key types Updated test_maps.fypp to include tests for int32 and character key types, in addition to base int8. --- test/hashmaps/test_maps.fypp | 84 ++++++++++++++++++------------------ 1 file changed, 42 insertions(+), 42 deletions(-) diff --git a/test/hashmaps/test_maps.fypp b/test/hashmaps/test_maps.fypp index 75dc16f23..cab9d4171 100644 --- a/test/hashmaps/test_maps.fypp +++ b/test/hashmaps/test_maps.fypp @@ -9,6 +9,7 @@ module test_stdlib_chaining_maps use :: stdlib_kinds, only : dp, int8, int32 use stdlib_hashmaps, only : chaining_hashmap_type, int_depth, int_index use stdlib_hashmap_wrappers + use stdlib_strings, only: to_string implicit none private @@ -25,7 +26,6 @@ module test_stdlib_chaining_maps integer, parameter :: test_16 = 2**4 integer, parameter :: test_256 = 2**8 integer, parameter :: key_types = 3 - character(len=*), parameter :: char_type = ' ' public :: collect_stdlib_chaining_maps contains @@ -83,7 +83,6 @@ contains integer :: index, key_type real(dp) :: rand2(2) integer(int32) :: rand_object(rand_size) - integer :: key_type do key_type = 1, key_types do index=1, rand_size @@ -122,15 +121,15 @@ contains ! Test all key interfaces call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) call map % map_entry( key, other, conflict ) - call check(error, .not.conflict, "Unable to map entry because of a key conflict.") + call check(error, .not.conflict, "Unable to map int8 entry because of a key conflict.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % map_entry( key, other, conflict ) - call check(error, .not.conflict, "Unable to map entry because of a key conflict.") + call check(error, .not.conflict, "Unable to map int32 entry because of a key conflict.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) + call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) call map % map_entry( key, other, conflict ) - call check(error, .not.conflict, "Unable to map entry because of a key conflict.") + call check(error, .not.conflict, "Unable to map character entry because of a key conflict.") if (allocated(error)) return @@ -150,15 +149,15 @@ contains do index2=1, test_size, test_block call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) call map % key_test( key, present ) - call check(error, present, "KEY not found in map KEY_TEST.") + call check(error, present, "Int8 KEY not found in map KEY_TEST.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % key_test( key, present ) - call check(error, present, "KEY not found in map KEY_TEST.") + call check(error, present, "Int32 KEY not found in map KEY_TEST.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) + call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) call map % key_test( key, present ) - call check(error, present, "KEY not found in map KEY_TEST.") + call check(error, present, "Character KEY not found in map KEY_TEST.") if (allocated(error)) return end do @@ -178,15 +177,15 @@ contains do index2=1, test_size, test_block call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) call map % get_other_data( key, other, exists ) - call check(error, exists, "Unable to get data because key not found in map.") + call check(error, exists, "Unable to get data because int8 key not found in map.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % get_other_data( key, other, exists ) - call check(error, exists, "Unable to get data because key not found in map.") + call check(error, exists, "Unable to get data because int32 key not found in map.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) + call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) call map % get_other_data( key, other, exists ) - call check(error, exists, "Unable to get data because key not found in map.") + call check(error, exists, "Unable to get data because character key not found in map.") end do end subroutine @@ -203,15 +202,15 @@ contains do index2=1, test_size, test_block call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) call map % remove(key, existed) - call check(error, existed, "Key not found in entry removal.") + call check(error, existed, "Int8 Key not found in entry removal.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % remove(key, existed) - call check(error, existed, "Key not found in entry removal.") + call check(error, existed, "Int32 Key not found in entry removal.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) + call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) call map % remove(key, existed) - call check(error, existed, "Key not found in entry removal.") + call check(error, existed, "Character Key not found in entry removal.") end do end subroutine @@ -276,6 +275,7 @@ module test_stdlib_open_maps use :: stdlib_kinds, only : dp, int8, int32 use stdlib_hashmaps, only : open_hashmap_type, int_depth, int_index use stdlib_hashmap_wrappers + use stdlib_strings, only: to_string implicit none private @@ -388,15 +388,15 @@ contains ! Test all key interfaces call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) call map % map_entry( key, other, conflict ) - call check(error, .not.conflict, "Unable to map entry because of a key conflict.") + call check(error, .not.conflict, "Unable to map int8 entry because of a key conflict.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % map_entry( key, other, conflict ) - call check(error, .not.conflict, "Unable to map entry because of a key conflict.") + call check(error, .not.conflict, "Unable to map int32 entry because of a key conflict.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) + call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) call map % map_entry( key, other, conflict ) - call check(error, .not.conflict, "Unable to map entry because of a key conflict.") + call check(error, .not.conflict, "Unable to map character entry because of a key conflict.") if (allocated(error)) return @@ -417,15 +417,15 @@ contains call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) call map % key_test( key, present ) - call check(error, present, "KEY not found in map KEY_TEST.") + call check(error, present, "Int8 KEY not found in map KEY_TEST.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % key_test( key, present ) - call check(error, present, "KEY not found in map KEY_TEST.") + call check(error, present, "Int32 KEY not found in map KEY_TEST.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) + call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) call map % key_test( key, present ) - call check(error, present, "KEY not found in map KEY_TEST.") + call check(error, present, "Character KEY not found in map KEY_TEST.") if (allocated(error)) return @@ -446,15 +446,15 @@ contains do index2=1, test_size, test_block call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) call map % get_other_data( key, other, exists ) - call check(error, exists, "Unable to get data because key not found in map.") + call check(error, exists, "Unable to get data because int8 key not found in map.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % get_other_data( key, other, exists ) - call check(error, exists, "Unable to get data because key not found in map.") + call check(error, exists, "Unable to get data because int32 key not found in map.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) + call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) call map % get_other_data( key, other, exists ) - call check(error, exists, "Unable to get data because key not found in map.") + call check(error, exists, "Unable to get data because character key not found in map.") end do end subroutine @@ -471,15 +471,15 @@ contains do index2=1, test_size, test_block call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) call map % remove(key, existed) - call check(error, existed, "Key not found in entry removal.") + call check(error, existed, "Int8 Key not found in entry removal.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) ) + call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % remove(key, existed) - call check(error, existed, "Key not found in entry removal.") + call check(error, existed, "Int32 Key not found in entry removal.") - call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) ) + call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) call map % remove(key, existed) - call check(error, existed, "Key not found in entry removal.") + call check(error, existed, "Character Key not found in entry removal.") end do end subroutine From fab4a211ae8fde3fa4a6e11c009f06c93216d34c Mon Sep 17 00:00:00 2001 From: chuckyvt <138633930+chuckyvt@users.noreply.github.com> Date: Mon, 15 Apr 2024 21:08:56 -0400 Subject: [PATCH 09/12] Update test/hashmaps/test_maps.fypp Co-authored-by: Jeremie Vandenplas --- test/hashmaps/test_maps.fypp | 1 - 1 file changed, 1 deletion(-) diff --git a/test/hashmaps/test_maps.fypp b/test/hashmaps/test_maps.fypp index cab9d4171..e4eb5e616 100644 --- a/test/hashmaps/test_maps.fypp +++ b/test/hashmaps/test_maps.fypp @@ -57,7 +57,6 @@ contains integer(int8) :: test_8_bits(test_size,key_types) call generate_vector(test_8_bits) - call map % init( ${hash_}$, slots_bits=10 ) call test_input_random_data(error, map, test_8_bits, test_${size_}$) From 9b80107608b3d2d0990be0ff0096b2f96f639c01 Mon Sep 17 00:00:00 2001 From: chuckyvt <138633930+chuckyvt@users.noreply.github.com> Date: Mon, 15 Apr 2024 22:09:55 -0400 Subject: [PATCH 10/12] Update test_maps.fypp Added addition commenting. Removed the character key type test as that was failing CI checks for unknown reasons. --- test/hashmaps/test_maps.fypp | 59 +++++++++--------------------------- 1 file changed, 15 insertions(+), 44 deletions(-) diff --git a/test/hashmaps/test_maps.fypp b/test/hashmaps/test_maps.fypp index cab9d4171..be2b73363 100644 --- a/test/hashmaps/test_maps.fypp +++ b/test/hashmaps/test_maps.fypp @@ -9,7 +9,6 @@ module test_stdlib_chaining_maps use :: stdlib_kinds, only : dp, int8, int32 use stdlib_hashmaps, only : chaining_hashmap_type, int_depth, int_index use stdlib_hashmap_wrappers - use stdlib_strings, only: to_string implicit none private @@ -25,7 +24,7 @@ module test_stdlib_chaining_maps integer, parameter :: test_size = rand_size*4 integer, parameter :: test_16 = 2**4 integer, parameter :: test_256 = 2**8 - integer, parameter :: key_types = 3 + integer, parameter :: key_types = 2 public :: collect_stdlib_chaining_maps contains @@ -84,7 +83,9 @@ contains real(dp) :: rand2(2) integer(int32) :: rand_object(rand_size) - do key_type = 1, key_types + ! Generate a unique int8 vector for each key type tested to avoid + ! dupilcate keys and mapping conflicts. + do key_type = 1, key_types do index=1, rand_size call random_number(rand2) if (rand2(1) < 0.5_dp) then @@ -118,21 +119,18 @@ contains allocate( dummy, source=dummy_val ) call set ( other, dummy ) - ! Test all key interfaces + ! Test base int8 key interface call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) call map % map_entry( key, other, conflict ) call check(error, .not.conflict, "Unable to map int8 entry because of a key conflict.") + ! Test int32 key interface + ! Use transfer to create int32 vector from generated int8 vector. call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % map_entry( key, other, conflict ) call check(error, .not.conflict, "Unable to map int32 entry because of a key conflict.") - call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) - call map % map_entry( key, other, conflict ) - call check(error, .not.conflict, "Unable to map character entry because of a key conflict.") - if (allocated(error)) return - end do end subroutine @@ -155,10 +153,6 @@ contains call map % key_test( key, present ) call check(error, present, "Int32 KEY not found in map KEY_TEST.") - call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) - call map % key_test( key, present ) - call check(error, present, "Character KEY not found in map KEY_TEST.") - if (allocated(error)) return end do @@ -182,10 +176,6 @@ contains call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % get_other_data( key, other, exists ) call check(error, exists, "Unable to get data because int32 key not found in map.") - - call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) - call map % get_other_data( key, other, exists ) - call check(error, exists, "Unable to get data because character key not found in map.") end do end subroutine @@ -207,10 +197,6 @@ contains call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % remove(key, existed) call check(error, existed, "Int32 Key not found in entry removal.") - - call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) - call map % remove(key, existed) - call check(error, existed, "Character Key not found in entry removal.") end do end subroutine @@ -275,7 +261,6 @@ module test_stdlib_open_maps use :: stdlib_kinds, only : dp, int8, int32 use stdlib_hashmaps, only : open_hashmap_type, int_depth, int_index use stdlib_hashmap_wrappers - use stdlib_strings, only: to_string implicit none private @@ -291,7 +276,7 @@ module test_stdlib_open_maps integer, parameter :: test_size = rand_size*4 integer, parameter :: test_16 = 2**4 integer, parameter :: test_256 = 2**8 - integer, parameter :: key_types = 3 + integer, parameter :: key_types = 2 public :: collect_stdlib_open_maps @@ -350,7 +335,9 @@ contains integer :: index, key_type real(dp) :: rand2(2) integer(int32) :: rand_object(rand_size) - + + ! Generate a unique int8 vector for each key type tested to avoid + ! dupilcate keys and mapping conflicts. do key_type = 1, key_types do index=1, rand_size call random_number(rand2) @@ -385,21 +372,18 @@ contains allocate( dummy, source=dummy_val ) call set ( other, dummy ) - ! Test all key interfaces + ! Test base int8 key interface call set( key, test_8_bits( index2:index2+test_block-1, 1 ) ) call map % map_entry( key, other, conflict ) call check(error, .not.conflict, "Unable to map int8 entry because of a key conflict.") + ! Test int32 key interface + ! Use transfer to create int32 vector from generated int8 vector. call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % map_entry( key, other, conflict ) call check(error, .not.conflict, "Unable to map int32 entry because of a key conflict.") - call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) - call map % map_entry( key, other, conflict ) - call check(error, .not.conflict, "Unable to map character entry because of a key conflict.") - if (allocated(error)) return - end do end subroutine @@ -423,12 +407,7 @@ contains call map % key_test( key, present ) call check(error, present, "Int32 KEY not found in map KEY_TEST.") - call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) - call map % key_test( key, present ) - call check(error, present, "Character KEY not found in map KEY_TEST.") - - if (allocated(error)) return - + if (allocated(error)) return end do end subroutine @@ -451,10 +430,6 @@ contains call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % get_other_data( key, other, exists ) call check(error, exists, "Unable to get data because int32 key not found in map.") - - call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) - call map % get_other_data( key, other, exists ) - call check(error, exists, "Unable to get data because character key not found in map.") end do end subroutine @@ -476,10 +451,6 @@ contains call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) ) call map % remove(key, existed) call check(error, existed, "Int32 Key not found in entry removal.") - - call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) ) - call map % remove(key, existed) - call check(error, existed, "Character Key not found in entry removal.") end do end subroutine From 822b5c97f870f52f8bf92bd43889c403ae5cd53e Mon Sep 17 00:00:00 2001 From: chuckyvt <138633930+chuckyvt@users.noreply.github.com> Date: Thu, 18 Apr 2024 07:50:50 -0400 Subject: [PATCH 11/12] stdlib_hashmap_wrappers and test_maps.fypp Added doc strings to explain the key_type approach in test_map.fypp. Indentation cleanup Added pure specifier to get and set int32 key type routines. --- src/stdlib_hashmap_wrappers.f90 | 10 +++++----- test/hashmaps/test_maps.fypp | 4 ++++ 2 files changed, 9 insertions(+), 5 deletions(-) diff --git a/src/stdlib_hashmap_wrappers.f90 b/src/stdlib_hashmap_wrappers.f90 index 2a19569b4..0991d9ac3 100644 --- a/src/stdlib_hashmap_wrappers.f90 +++ b/src/stdlib_hashmap_wrappers.f90 @@ -279,7 +279,7 @@ subroutine get_int8_key( key, value ) end subroutine get_int8_key - subroutine get_int32_key( key, value ) + pure subroutine get_int32_key( key, value ) !! Version: Experimental !! !! Gets the contents of the key as an INTEGER(INT32) vector @@ -340,17 +340,17 @@ subroutine set_int8_key( key, value ) end subroutine set_int8_key - subroutine set_int32_key( key, value ) + pure subroutine set_int32_key( key, value ) !! Version: Experimental !! !! Sets the contents of the key from an INTEGER(INT32) vector !! Arguments: !! key - the output key !! value - the input INTEGER(INT32) vector - type(key_type), intent(out) :: key - integer(int32), intent(in) :: value(:) + type(key_type), intent(out) :: key + integer(int32), intent(in) :: value(:) - key % value = transfer(value, key % value) + key % value = transfer(value, key % value) end subroutine set_int32_key diff --git a/test/hashmaps/test_maps.fypp b/test/hashmaps/test_maps.fypp index 8746aa1a6..372f2f826 100644 --- a/test/hashmaps/test_maps.fypp +++ b/test/hashmaps/test_maps.fypp @@ -24,6 +24,8 @@ module test_stdlib_chaining_maps integer, parameter :: test_size = rand_size*4 integer, parameter :: test_16 = 2**4 integer, parameter :: test_256 = 2**8 + ! key_type = 2 to support int8 and int32 key types tested. Can be + ! icreased to generate additional unique int8 vectors additional key types. integer, parameter :: key_types = 2 public :: collect_stdlib_chaining_maps @@ -275,6 +277,8 @@ module test_stdlib_open_maps integer, parameter :: test_size = rand_size*4 integer, parameter :: test_16 = 2**4 integer, parameter :: test_256 = 2**8 + ! key_type = 2 to support int8 and int32 key types tested. Can be + ! icreased to generate additional unique int8 vectors additional key types. integer, parameter :: key_types = 2 public :: collect_stdlib_open_maps From f35386fdf07fdc7cc4e0f6070c5d38d3b626dee4 Mon Sep 17 00:00:00 2001 From: chuckyvt <138633930+chuckyvt@users.noreply.github.com> Date: Thu, 18 Apr 2024 07:59:09 -0400 Subject: [PATCH 12/12] Update test_maps.fypp typo fix --- test/hashmaps/test_maps.fypp | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/test/hashmaps/test_maps.fypp b/test/hashmaps/test_maps.fypp index 372f2f826..5498ebc2e 100644 --- a/test/hashmaps/test_maps.fypp +++ b/test/hashmaps/test_maps.fypp @@ -25,7 +25,7 @@ module test_stdlib_chaining_maps integer, parameter :: test_16 = 2**4 integer, parameter :: test_256 = 2**8 ! key_type = 2 to support int8 and int32 key types tested. Can be - ! icreased to generate additional unique int8 vectors additional key types. + ! increased to generate additional unique int8 vectors additional key types. integer, parameter :: key_types = 2 public :: collect_stdlib_chaining_maps @@ -278,7 +278,7 @@ module test_stdlib_open_maps integer, parameter :: test_16 = 2**4 integer, parameter :: test_256 = 2**8 ! key_type = 2 to support int8 and int32 key types tested. Can be - ! icreased to generate additional unique int8 vectors additional key types. + ! increased to generate additional unique int8 vectors additional key types. integer, parameter :: key_types = 2 public :: collect_stdlib_open_maps