@@ -89,8 +89,10 @@ module stdlib_64_bit_hash_codes
8989 end type spooky_subhash
9090
9191 interface fnv_1_hash
92+ !! Version: experimental
93+ !!
9294!! FNV_1 interfaces
93-
95+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#fnv_1-calculates-a-hash-code-from-a-key))
9496 #:for k1 in INT_KINDS
9597 pure module function ${k1}$_fnv_1( key ) result(hash_code)
9698!! FNV_1 hash function for rank 1 arrays of kind ${k1}$
@@ -109,7 +111,10 @@ module stdlib_64_bit_hash_codes
109111
110112
111113 interface fnv_1a_hash
114+ !! Version: experimental
115+ !!
112116!! FNV_1A interfaces
117+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#fnv_1a-calculates-a-hash-code-from-a-key))
113118 #:for k1 in INT_KINDS
114119 pure module function ${k1}$_fnv_1a( key ) result(hash_code)
115120!! FNV_1A hash function for rank 1 arrays of kind ${k1}$
@@ -127,8 +132,10 @@ module stdlib_64_bit_hash_codes
127132 end interface fnv_1a_hash
128133
129134 interface spooky_hash
135+ !! Version: experimental
136+ !!
130137!! SPOOKY_HASH interfaces
131-
138+ !!([Specification](../page/specs/stdlib_hash_procedures.html#spooky_hash-maps-a-character-string-or-integer-vector-to-an-integer))
132139 #:for k1 in INT_KINDS
133140 module function ${k1}$_spooky_hash( key, seed ) &
134141 result(hash_code)
@@ -152,6 +159,8 @@ module stdlib_64_bit_hash_codes
152159 interface
153160
154161 module subroutine spookyHash_128( key, hash_inout )
162+ !! Version: experimental
163+ !!
155164 integer(int8), intent(in), target :: key(0:)
156165 integer(int_hash), intent(inout) :: hash_inout(2)
157166 end subroutine spookyHash_128
@@ -160,6 +169,8 @@ module stdlib_64_bit_hash_codes
160169
161170
162171 interface spooky_init
172+ !! Version: experimental
173+ !!
163174
164175 pure module subroutine spookysubhash_init( self, seed )
165176 type(spooky_subhash), intent(out) :: self
@@ -172,6 +183,8 @@ module stdlib_64_bit_hash_codes
172183 interface spooky_update
173184
174185 module subroutine spookyhash_update( spooky, key )
186+ !! Version: experimental
187+ !!
175188 type(spooky_subhash), intent(inout) :: spooky
176189 integer(int8), intent(in) :: key(0:)
177190 end subroutine spookyhash_update
@@ -182,6 +195,8 @@ module stdlib_64_bit_hash_codes
182195 interface spooky_final
183196
184197 module subroutine spookyhash_final(spooky, hash_code)
198+ !! Version: experimental
199+ !!
185200 type(spooky_subhash), intent(inout) :: spooky
186201 integer(int_hash), intent(inout) :: hash_code(2)
187202 end subroutine spookyhash_final
@@ -191,15 +206,19 @@ module stdlib_64_bit_hash_codes
191206interface
192207
193208 module subroutine new_spooky_hash_seed( seed )
194- ! Random SEED generator for
209+ !! Version: experimental
210+ !!
211+ !! Random SEED generator for
195212 integer(int64), intent(inout) :: seed(2)
196213 end subroutine new_spooky_hash_seed
197214
198215 end interface
199216
200217 interface pengy_hash
218+ !! Version: experimental
219+ !!
201220!! PENGY_HASH interfaces
202-
221+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#pengy_hash-maps-a-character-string-or-integer-vector-to-an-integer))
203222 #:for k1 in INT_KINDS
204223 pure module function ${k1}$_pengy_hash( key, seed ) result(hash_code)
205224!! PENGY_HASH hash function for rank 1 array keys of kind ${k1}$
@@ -222,7 +241,9 @@ interface
222241 interface
223242
224243 module subroutine new_pengy_hash_seed( seed )
225- ! Random SEED generator for MIR_HASH_STRICT
244+ !! Version: experimental
245+ !!
246+ !! Random SEED generator for MIR_HASH_STRICT
226247 integer(int32), intent(inout) :: seed
227248 end subroutine new_pengy_hash_seed
228249
@@ -231,8 +252,12 @@ interface
231252contains
232253
233254 elemental function fibonacci_hash( key, nbits ) result( sample )
255+ !! Version: experimental
256+ !!
234257!! Maps the 64 bit integer KEY to an unsigned integer value with only NBITS
235258!! bits where NBITS is less than 64
259+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#fibonacci_hash-maps-an-integer-to-a-smaller-number-of-bits_1))
260+
236261 integer(int64), intent(in) :: key
237262 integer, intent(in) :: nbits
238263 integer(int64) :: sample
@@ -242,8 +267,12 @@ contains
242267 end function fibonacci_hash
243268
244269 elemental function universal_mult_hash( key, seed, nbits ) result( sample )
270+ !! Version: experimental
271+ !!
245272!! Uses the "random" odd 64 bit integer SEED to map the 64 bit integer KEY to
246273!! an unsigned integer value with only NBITS bits where NBITS is less than 64.
274+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#universal_mult_hash-maps-an-integer-to-a-smaller-number-of-bits_1))
275+
247276 integer(int64), intent(in) :: key
248277 integer(int64), intent(in) :: seed
249278 integer, intent(in) :: nbits
@@ -254,8 +283,12 @@ contains
254283 end function universal_mult_hash
255284
256285 subroutine odd_random_integer( harvest )
286+ !! Version: experimental
287+ !!
257288!! Returns a 64 bit pseudo random integer, HARVEST, distributed uniformly over
258289!! the odd integers of the 64 bit kind.
290+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#odd_random_integer-returns-odd-integer))
291+
259292 integer(int64), intent(out) :: harvest
260293 real(dp) :: sample(2)
261294 integer(int32) :: part(2)
@@ -268,6 +301,8 @@ contains
268301 end subroutine odd_random_integer
269302
270303 subroutine random_integer( harvest )
304+ !! Version: experimental
305+ !!
271306!! Returns a 64 bit pseudo random integer, HARVEST, distributed uniformly over
272307!! the values of the 64 bit kind.
273308 integer(int64), intent(out) :: harvest
0 commit comments