@@ -21,7 +21,7 @@ This document discusses the hash maps in the Fortran Standard Library.
2121
2222The Fortran Standard Library is distributed under the MIT License.
2323However components of the library should be evaluated as to whether
24- they are compatible with the MTI License.
24+ they are compatible with the MIT License.
2525The current hash maps were inspired by an
2626[ implementation] ( http://chasewoerner.org/src/hasht/ ) of David
2727Chase. While the code has been greatly modified from his
@@ -229,14 +229,14 @@ is an `intent(out)` argument.
229229``` fortran
230230 program demo_copy_key
231231 use stdlib_hashmap_wrappers, only: &
232- copy_key, operator(==), key_type
232+ copy_key, operator(==), key_type, set
233233 use iso_fortran_env, only: int8
234234 implicit none
235235 integer(int8) :: i, value(15)
236236 type(key_type) :: old_key, new_key
237237 value = [(i, i = 1, 15)]
238- call set( key_out , value )
239- call copy_key( key_out , new_key )
238+ call set( old_key , value )
239+ call copy_key( old_key , new_key )
240240 print *, "old_key == new_key = ", old_key == new_key
241241 end program demo_copy_key
242242```
@@ -271,26 +271,24 @@ is an `intent(out)` argument.
271271
272272``` fortran
273273 program demo_copy_other
274- use stdlib_hashmap_wrappers, only: &
275- copy_other, get, other_type, set
274+ use stdlib_hashmap_wrappers, only: copy_other, other_type
276275 use iso_fortran_env, only: int8
277276 implicit none
278277 type(other_type) :: other_in, other_out
279- integer(int_8) :: i
280- class(*), allocatable :: dummy
278+ integer(int8) :: i
281279 type dummy_type
282280 integer(int8) :: value(15)
283281 end type
284282 type(dummy_type) :: dummy_val
285- do i= 1, 15
283+ do i = 1, 15
286284 dummy_val % value1(i) = i
287285 end do
288286 allocate(other_in % value, source=dummy_val)
289287 call copy_other( other_in, other_out )
290- select type(other_out)
291- type(dummy_type)
288+ select type(out => other_out % value )
289+ type is (dummy_type)
292290 print *, "other_in == other_out = ", &
293- all( dummy_val % value == other_out % value )
291+ all( dummy_val % value == out % value )
294292 end select
295293 end program demo_copy_other
296294```
@@ -507,19 +505,19 @@ is an `intent(out)` argument.
507505``` fortran
508506 program demo_free_other
509507 use stdlib_hashmap_wrappers, only: &
510- copy_other, free_other, other_type, set
508+ copy_other, free_other, other_type
511509 use iso_fortran_env, only: int8
512510 implicit none
513511 type dummy_type
514512 integer(int8) :: value(15)
515513 end type dummy_type
516- typer (dummy_type) :: dummy_val
514+ type (dummy_type) :: dummy_val
517515 type(other_type), allocatable :: other_in, other_out
518- integer(int_8 ) :: i
516+ integer(int8 ) :: i
519517 do i=1, 15
520518 dummy_val % value(i) = i
521519 end do
522- allocate(other_in, source=dummy_val)
520+ allocate(other_in % value , source=dummy_val)
523521 call copy_other( other_in, other_out )
524522 call free_other( other_out )
525523 end program demo_free_other
@@ -573,7 +571,7 @@ an allocatable of `class(*)`. It is an `intent(out)` argument.
573571 implicit none
574572 integer(int8), allocatable :: value(:), result(:)
575573 type(key_type) :: key
576- integer(int_8 ) :: i
574+ integer(int8 ) :: i
577575 allocate( value(1:15) )
578576 do i=1, 15
579577 value(i) = i
@@ -585,7 +583,7 @@ an allocatable of `class(*)`. It is an `intent(out)` argument.
585583```
586584
587585
588- #### ` hasher_fun ` - serves aa a function prototype.
586+ #### ` hasher_fun ` - serves as a function prototype.
589587
590588##### Status
591589
@@ -933,7 +931,7 @@ value to an `int8` vector.
933931 implicit none
934932 integer(int8), allocatable :: value(:), result(:)
935933 type(key_type) :: key
936- integer(int_8 ) :: i
934+ integer(int8 ) :: i
937935 allocate( value(1:15) )
938936 do i=1, 15
939937 value(i) = i
@@ -1392,7 +1390,7 @@ The result will be the number of procedure calls on the hash map.
13921390 use stdlib_hashmap_wrappers, only: fnv_1_hasher
13931391 implicit none
13941392 type(chaining_hashmap_type) :: map
1395- type (int_calls) :: initial_calls
1393+ integer (int_calls) :: initial_calls
13961394 call map % init( fnv_1_hasher )
13971395 initial_calls = map % calls()
13981396 print *, "INITIAL_CALLS = ", initial_calls
@@ -1518,9 +1516,9 @@ undefined.
15181516 end if
15191517 call get( other, data )
15201518 select type( data )
1521- type (dummy_type)
1519+ type is (dummy_type)
15221520 print *, 'Other data % value = ', data % value
1523- type default
1521+ class default
15241522 print *, 'Invalid data type in other'
15251523 end select
15261524 end program demo_get_other_data
@@ -1565,7 +1563,7 @@ Subroutine
15651563 error code.
15661564
15671565* If ` slots_bits ` is absent then the effective value for ` slots_bits `
1568- is ` default_slots_bits ` .
1566+ is ` default_bits ` .
15691567
15701568` status ` (optional): shall be a scalar integer variable of kind
15711569` int32 ` . It is an ` intent(out) ` argument. On return if present it
@@ -1587,11 +1585,11 @@ has the value `alloc_fault`.
15871585
15881586``` fortran
15891587 program demo_init
1590- use stdlib_hashmaps, only: chaining_map_type
1588+ use stdlib_hashmaps, only: chaining_hashmap_type
15911589 use stdlib_hashmap_wrappers, only: fnv_1_hasher
1592- type(fnv_1a_type) :: fnv_1
1593- type(chaining_map_type ) :: map
1594- call map % init( fnv_1a , slots_bits=10 )
1590+ implicit none
1591+ type(chaining_hashmap_type ) :: map
1592+ call map % init( fnv_1_hasher , slots_bits=10 )
15951593 end program demo_init
15961594```
15971595
@@ -1748,7 +1746,7 @@ is ignored.
17481746 program demo_map_entry
17491747 use, intrinsic:: iso_fortran_env, only: int8
17501748 use stdlib_hashmaps, only: chaining_hashmap_type
1751- use stdlib_hashmap_wrappers, only: fnv_1_hasher, key_type, other_type
1749+ use stdlib_hashmap_wrappers, only: fnv_1_hasher, key_type, other_type, set
17521750 type(chaining_hashmap_type) :: map
17531751 type(key_type) :: key
17541752 logical :: conflict
@@ -1806,7 +1804,7 @@ rehashing.
18061804 type(chaining_hashmap_type) :: map
18071805 real :: nprobes
18081806 call map % init( fnv_1_hasher )
1809- nprobes = map % probes ()
1807+ nprobes = map % map_probes ()
18101808 print *, "Initial probes = ", nprobes
18111809 end program demo_probes
18121810```
@@ -1855,7 +1853,7 @@ The result is the number of slots in `map`.
18551853 call map % init( fnv_1_hasher )
18561854 initial_slots = map % num_slots ()
18571855 print *, "Initial slots = ", initial_slots
1858- end program num_slots
1856+ end program demo_num_slots
18591857```
18601858
18611859
@@ -1891,10 +1889,12 @@ It is the hash method to be used by `map`.
18911889
18921890``` fortran
18931891 program demo_rehash
1892+ use stdlib_kinds, only: int8
18941893 use stdlib_hashmaps, only: open_hashmap_type
1895- use stdlib_hasmap_wrappers, only: fnv_1_hasher, fnv_1a_hasher,&
1896- key_type, other_type
1897- type(openn_hashmap_type) :: map
1894+ use stdlib_hashmap_wrappers, only: fnv_1_hasher, fnv_1a_hasher,&
1895+ key_type, other_type, set
1896+ implicit none
1897+ type(open_hashmap_type) :: map
18981898 type(key_type) :: key
18991899 type(other_type) :: other
19001900 class(*), allocatable :: dummy
@@ -2009,20 +2009,23 @@ not exist and nothing was done.
20092009
20102010``` fortran
20112011 program demo_set_other_data
2012+ use stdlib_kinds, only: int8
20122013 use stdlib_hashmaps, only: open_hashmap_type
20132014 use stdlib_hashmap_wrappers, only: fnv_1_hasher, &
20142015 fnv_1a_hasher, key_type, other_type, set
2016+ implicit none
2017+ logical :: exists
20152018 type(open_hashmap_type) :: map
20162019 type(key_type) :: key
20172020 type(other_type) :: other
20182021 class(*), allocatable :: dummy
20192022 call map % init( fnv_1_hasher, slots_bits=10 )
2020- allocate( dummy, source='A value` )
2023+ allocate( dummy, source='A value' )
20212024 call set( key, [ 5_int8, 7_int8, 4_int8, 13_int8 ] )
20222025 call set( other, dummy )
20232026 call map % map_entry( key, other )
20242027 deallocate( dummy )
2025- allocate( dummy, source='Another value` )
2028+ allocate( dummy, source='Another value' )
20262029 call set( other, dummy )
20272030 call map % set_other_data( key, other, exists )
20282031 print *, 'The entry to have its other data replaced exists = ', exists
0 commit comments