@@ -118,7 +118,7 @@ opaque. Their current representations are as follows
118
118
119
119
type :: other_type
120
120
private
121
- integer(int8 ), allocatable :: value(:)
121
+ class(* ), allocatable :: value
122
122
end type other_type
123
123
```
124
124
@@ -141,39 +141,40 @@ Procedures to manipulate `key_type` data:
141
141
142
142
* ` equal_keys( key1, key2 ) ` - compares two keys for equality.
143
143
144
- * ` get( key, value ) ` - extracts the contents of key into value, an
145
- ` int8 ` array or character string.
144
+ * ` get( key, value ) ` - extracts the contents of ` key ` into ` value ` ,
145
+ an ` int8 ` array or character string.
146
146
147
- * ` free_key( key ) ` - frees the memory in key.
147
+ * ` free_key( key ) ` - frees the memory in ` key ` .
148
148
149
- * ` set( key, value ) ` - sets the content of key to value.
149
+ * ` set( key, value ) ` - sets the content of ` key ` to ` value ` .
150
150
151
151
Procedures to manipulate ` other_type ` data:
152
152
153
153
* ` copy_other( other_in, other_out ) ` - Copies the contents of the
154
154
other data, ` other_in ` , to the contents of the other data,
155
155
` other_out ` .
156
156
157
- * ` get( other, value ) ` - extracts the contents of other into value, an
158
- ` int8 ` array or character string.
157
+ * ` get( other, value ) ` - extracts the contents of ` other ` into the
158
+ class( * ) variable ` value ` .
159
159
160
- * ` set( other, value ) ` - sets to content of other to value.
160
+ * ` set( other, value ) ` - sets the content of ` other ` to the class(* )
161
+ variable ` value ` .
161
162
162
- * ` free_other( other ) ` - frees the memory in other.
163
+ * ` free_other( other ) ` - frees the memory in ` other ` .
163
164
164
165
Procedures to hash keys to 32 bit integers:
165
166
166
- * ` fnv_1_hasher( key ) ` - hashes a key using the FNV-1 algorithm.
167
+ * ` fnv_1_hasher( key ) ` - hashes a ` key ` using the FNV-1 algorithm.
167
168
168
- * ` fnv_1a_hasher( key ) ` - hashes a key using the FNV-1a algorithm.
169
+ * ` fnv_1a_hasher( key ) ` - hashes a ` key ` using the FNV-1a algorithm.
169
170
170
- * ` seeded_nmhash32_hasher( key ) ` - hashes a key using the nmhash32
171
+ * ` seeded_nmhash32_hasher( key ) ` - hashes a ` key ` using the nmhash32
171
172
algorithm.
172
173
173
- * ` seeded_nmhash32x_hasher( key ) ` - hashes a key using the nmhash32x
174
+ * ` seeded_nmhash32x_hasher( key ) ` - hashes a ` key ` using the nmhash32x
174
175
algorithm.
175
176
176
- * ` seeded_water_hasher( key ) ` - hashes a key using the waterhash
177
+ * ` seeded_water_hasher( key ) ` - hashes a ` key ` using the waterhash
177
178
algorithm.
178
179
179
180
### Specifications of the ` stdlib_hashmap_wrappers ` procedures
@@ -186,7 +187,7 @@ Experimental
186
187
187
188
##### Description
188
189
189
- Returns a copy of an input of type ` key_type `
190
+ Returns a copy of an input of type ` key_type ` .
190
191
191
192
##### Syntax
192
193
@@ -233,7 +234,7 @@ Experimental
233
234
234
235
##### Description
235
236
236
- Returns a copy of an input of type ` other_type `
237
+ Returns a copy of an input of type ` other_type ` .
237
238
238
239
##### Syntax
239
240
@@ -259,18 +260,23 @@ is an `intent(out)` argument.
259
260
copy_other, get, other_type, set
260
261
use iso_fortran_env, only: int8
261
262
implicit none
262
- integer(int8), allocatable :: value1(:), value2(:)
263
263
type(other_type) :: other_in, other_out
264
264
integer(int_8) :: i
265
- allocate( value1(1:15) )
265
+ class(*), allocatable :: dummy
266
+ type dummy_type
267
+ integer(int8) :: value(15)
268
+ end type
269
+ type(dummy_type) :: dummy_val
266
270
do i=1, 15
267
- value1(i) = i
271
+ dummy_val % value1(i) = i
268
272
end do
269
- call set( other_in, value1 )
273
+ allocate( other_in % value, source=dummy_val )
270
274
call copy_other( other_in, other_out )
271
- call get( other_out, value2 )
272
- print *, "other_in == other_out = ", &
273
- all( value1 == value2 )
275
+ select type(other_out)
276
+ type(dummy_type)
277
+ print *, "other_in == other_out = ", &
278
+ all( dummy_val % value == other_out % value )
279
+ end select
274
280
end program demo_copy_other
275
281
```
276
282
@@ -282,7 +288,7 @@ Experimental
282
288
283
289
##### Description
284
290
285
- Returns ` .true. ` if two keys are equal, and false otherwise.
291
+ Returns ` .true. ` if two keys are equal, and ` . false. ` otherwise.
286
292
287
293
##### Syntax
288
294
@@ -548,14 +554,16 @@ is an `intent(out)` argument.
548
554
copy_other, free_other, other_type, set
549
555
use iso_fortran_env, only: int8
550
556
implicit none
551
- integer(int8), allocatable :: value(:)
552
- type(key_type) :: other_in, other_out
557
+ type dummy_type
558
+ integer(int8) :: value(15)
559
+ end type dummy_type
560
+ typer(dummy_type) :: dummy_val
561
+ type(other_type), allocatable :: other_in, other_out
553
562
integer(int_8) :: i
554
- allocate( value(1:15) )
555
563
do i=1, 15
556
- value(i) = i
564
+ dummy_val % value(i) = i
557
565
end do
558
- call set( other_in, value )
566
+ allocate( other_in, source=dummy_val )
559
567
call copy_other( other_in, other_out )
560
568
call free_other( other_out )
561
569
end program demo_free_other
@@ -570,8 +578,8 @@ Experimental
570
578
571
579
##### Description
572
580
573
- Extracts the data from a ` key_type ` or an ` other_type ` and stores it
574
- in the variable ` value ` ..
581
+ Extracts the data from a ` key_type ` or ` other_type ` and stores it
582
+ in the variable ` value ` .
575
583
576
584
##### Syntax
577
585
581
589
582
590
` call [[stdlib_hashmap_wrappers:get]]( other, value ) `
583
591
584
-
585
592
##### Class
586
593
587
594
Subroutine.
@@ -594,9 +601,11 @@ is an `intent(in)` argument.
594
601
` other ` : shall be a scalar expression of type ` other_type ` . It
595
602
is an ` intent(in) ` argument.
596
603
597
- ` value ` : shall be an allocatable default character string variable, or
598
- an allocatable vector variable of type integer and kind ` int8 ` . It is
599
- an ` intent(out) ` argument.
604
+ ` value ` : if the the first argument is of ` key_type ` ` value ` shall be
605
+ an allocatable default character string variable, or
606
+ an allocatable vector variable of type integer and kind ` int8 ` ,
607
+ otherwise the first argument is of ` other_type ` and ` value ` shall be
608
+ an allocatable of ` class(*) ` . It is an ` intent(out) ` argument.
600
609
601
610
##### Example
602
611
@@ -629,7 +638,7 @@ Experimental
629
638
##### Description
630
639
631
640
Serves as a prototype for hashing functions with a single, ` key ` ,
632
- argument returning an ` int32 ` hash value.
641
+ argument of type ` key_type ` returning an ` int32 ` hash value.
633
642
634
643
##### Syntax
635
644
@@ -894,9 +903,10 @@ is an `intent(out)` argument.
894
903
` other ` : shall be a scalar variable of type ` other_type ` . It
895
904
is an ` intent(out) ` argument.
896
905
897
- ` value ` : shall be a default character string expression, or a
898
- vector expression of type integer and kind ` int8 ` . It is an
899
- ` intent(in) ` argument.
906
+ ` value ` : if the first argument is ` key ` ` vaalue ` shall be a default
907
+ character string expression, or a vector expression of type integer
908
+ and kind ` int8 ` , while for a first argument of type ` other ` ` value `
909
+ shall be of type ` class(*) ` . It is an ` intent(in) ` argument.
900
910
901
911
##### Example
902
912
0 commit comments