Skip to content

Commit b1cfb3b

Browse files
committed
Remove other type from test_chaining and test_open
1 parent b09a1ad commit b1cfb3b

File tree

2 files changed

+5
-12
lines changed

2 files changed

+5
-12
lines changed

test/hashmaps/test_chaining_maps.f90

Lines changed: 1 addition & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -161,22 +161,17 @@ subroutine input_random_data( map, test_block, hash_name, size_name )
161161
integer(int_index), intent(in) :: test_block
162162
character(*), intent(in) :: hash_name
163163
character(*), intent(in) :: size_name
164-
class(*), allocatable :: dummy
165164
type(dummy_type) :: dummy_val
166165
integer :: index2
167166
type(key_type) :: key
168-
type(other_type) :: other
169167
real :: t1, t2, tdiff
170168
logical :: conflict
171169

172170
call cpu_time(t1)
173171
do index2=1, size(test_8_bits), test_block
174172
call set( key, test_8_bits( index2:index2+test_block-1 ) )
175-
if (allocated(dummy)) deallocate(dummy)
176173
dummy_val % value = test_8_bits( index2:index2+test_block-1 )
177-
allocate( dummy, source=dummy_val )
178-
call set ( other, dummy )
179-
call map % map_entry( key, other, conflict )
174+
call map % map_entry( key, dummy_val, conflict )
180175
if (conflict) &
181176
error stop "Unable to map entry because of a key conflict."
182177
end do

test/hashmaps/test_open_maps.f90

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -162,22 +162,20 @@ subroutine input_random_data( map, test_block, hash_name, size_name )
162162
integer(int_index), intent(in) :: test_block
163163
character(*), intent(in) :: hash_name
164164
character(*), intent(in) :: size_name
165-
class(*), allocatable :: dummy
165+
166166
type(dummy_type) :: dummy_val
167167
integer :: index2
168168
type(key_type) :: key
169-
type(other_type) :: other
170169
real :: t1, t2, tdiff
171170
logical :: conflict
172171

173172
call cpu_time(t1)
174173
do index2=1, size(test_8_bits), test_block
175174
call set( key, test_8_bits( index2:index2+test_block-1 ) )
176-
if (allocated(dummy)) deallocate(dummy)
175+
177176
dummy_val % value = test_8_bits( index2:index2+test_block-1 )
178-
allocate( dummy, source=dummy_val )
179-
call set ( other, dummy )
180-
call map % map_entry( key, other, conflict )
177+
178+
call map % map_entry( key, dummy_val, conflict )
181179
if (conflict) &
182180
error stop "Unable to map entry because of a key conflict."
183181
end do

0 commit comments

Comments
 (0)