@@ -70,8 +70,10 @@ module stdlib_32_bit_hash_codes
7070
7171
7272 interface fnv_1_hash
73+ !! Version: experimental
74+ !!
7375!! FNV_1 interfaces
74-
76+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#fnv_1_hash-calculates-a-hash-code-from-a-key))
7577 #:for k1 in INT_KINDS
7678 pure module function ${k1}$_fnv_1( key ) result(hash_code)
7779!! FNV_1 hash function for rank 1 array keys of kind ${k1}$
@@ -90,7 +92,10 @@ module stdlib_32_bit_hash_codes
9092 end interface fnv_1_hash
9193
9294 interface fnv_1a_hash
95+ !! Version: experimental
96+ !!
9397!! FNV_1A interfaces
98+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#fnv_1a_hash-calculates-a-hash-code-from-a-key))
9499 #:for k1 in INT_KINDS
95100 pure module function ${k1}$_fnv_1a( key ) result(hash_value)
96101!! FNV_1A hash function for rank 1 array keys of kind ${k1}$
@@ -109,8 +114,10 @@ module stdlib_32_bit_hash_codes
109114 end interface fnv_1a_hash
110115
111116 interface nmhash32
112- !! NMHASH32 interfaces
113-
117+ !! Version: experimental
118+ !!
119+ !! NMHASH32 interfaces
120+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#nmhash32-calculates-a-hash-code-from-a-key-and-a-seed))
114121 #:for k1 in INT_KINDS
115122 pure module function ${k1}$_nmhash32( key, seed ) &
116123 result(hash_value)
@@ -133,8 +140,10 @@ module stdlib_32_bit_hash_codes
133140 end interface nmhash32
134141
135142 interface nmhash32x
136- !! NMHASH32X interfaces
137-
143+ !! Version: experimental
144+ !!
145+ !! NMHASH32X interfaces
146+ !! ([Specification](file:///home/jvandenp/stdlib/API-doc/page/specs/stdlib_hash_procedures.html#nmhash32x-calculates-a-hash-code-from-a-key-and-a-seed))
138147 #:for k1 in INT_KINDS
139148 pure module function ${k1}$_nmhash32x( key, seed ) &
140149 result(hash_value)
@@ -157,8 +166,10 @@ module stdlib_32_bit_hash_codes
157166 end interface nmhash32x
158167
159168 interface water_hash
169+ !! Version: experimental
170+ !!
160171!! WATER_HASH interfaces
161-
172+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#water_hash-calculates-a-hash-code-from-a-key-and-a-seed))
162173 #:for k1 in INT_KINDS
163174 pure module function ${k1}$_water_hash( key, seed ) &
164175 result(hash_code)
@@ -180,14 +191,19 @@ module stdlib_32_bit_hash_codes
180191 end interface water_hash
181192
182193 interface new_water_hash_seed
183-
194+ !! Version: experimental
195+ !!
196+ !! ([Specification](file:///home/jvandenp/stdlib/API-doc/page/specs/stdlib_hash_procedures.html#new_water_hash_seed-returns-a-valid-input-seed-for-water_hash))
184197 module subroutine new_water_hash_seed( seed )
185198 integer(int64), intent(inout) :: seed
186199 end subroutine new_water_hash_seed
187200
188201 end interface new_water_hash_seed
189202
190203 interface new_nmhash32_seed
204+ !! Version: experimental
205+ !!
206+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#new_nmhash32_seed-returns-a-valid-input-seed-for-nmhash32)
191207
192208 module subroutine new_nmhash32_seed( seed )
193209 integer(int32), intent(inout) :: seed
@@ -196,6 +212,9 @@ module stdlib_32_bit_hash_codes
196212 end interface new_nmhash32_seed
197213
198214 interface new_nmhash32x_seed
215+ !! Version: experimental
216+ !!
217+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#new_nmhash32x_seed-returns-a-valid-input-seed-for-nmhash32x))
199218
200219 module subroutine new_nmhash32x_seed( seed )
201220 integer(int32), intent(inout) :: seed
@@ -206,8 +225,12 @@ module stdlib_32_bit_hash_codes
206225contains
207226
208227 elemental function fibonacci_hash( key, nbits ) result( sample )
228+ !! Version: experimental
229+ !!
209230!! Maps the 32 bit integer KEY to an unsigned integer value with only NBITS
210231!! bits where NBITS is less than 32
232+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#fibonacci_hash-maps-an-integer-to-a-smaller-number-of-bits))
233+
211234 integer(int32), intent(in) :: key
212235 integer, intent(in) :: nbits
213236 integer(int32) :: sample
@@ -217,8 +240,11 @@ contains
217240 end function fibonacci_hash
218241
219242 elemental function universal_mult_hash( key, seed, nbits ) result( sample )
243+ !! Version: experimental
244+ !!
220245!! Uses the "random" odd 32 bit integer SEED to map the 32 bit integer KEY to
221246!! an unsigned integer value with only NBITS bits where NBITS is less than 32
247+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#universal_mult_hash-maps-an-integer-to-a-smaller-number-of-bits))
222248 integer(int32), intent(in) :: key
223249 integer(int32), intent(in) :: seed
224250 integer, intent(in) :: nbits
@@ -229,8 +255,11 @@ contains
229255 end function universal_mult_hash
230256
231257 subroutine odd_random_integer( harvest )
258+ !! Version: experimental
259+ !!
232260!! Returns a 32 bit pseudo random integer, HARVEST, distributed uniformly over
233261!! the odd integers of the INT32 kind.
262+ !! ([Specification](../page/specs/stdlib_hash_procedures.html#odd_random_integer-returns-an-odd-integer))
234263 integer(int32), intent(out) :: harvest
235264 real(dp) :: sample
236265
0 commit comments