1{- Convenience wrapper around cryptonite's hashing.
2 -
3 - Copyright 2013-2021 Joey Hess <id@joeyh.name>
4 -
5 - License: BSD-2-clause
6 -}
7
8{-# LANGUAGE BangPatterns #-}
9
10module Utility.Hash (
11	sha1,
12	sha1_context,
13	sha2_224,
14	sha2_224_context,
15	sha2_256,
16	sha2_256_context,
17	sha2_384,
18	sha2_384_context,
19	sha2_512,
20	sha2_512_context,
21	sha3_224,
22	sha3_224_context,
23	sha3_256,
24	sha3_256_context,
25	sha3_384,
26	sha3_384_context,
27	sha3_512,
28	sha3_512_context,
29	skein256,
30	skein256_context,
31	skein512,
32	skein512_context,
33	blake2s_160,
34	blake2s_160_context,
35	blake2s_224,
36	blake2s_224_context,
37	blake2s_256,
38	blake2s_256_context,
39	blake2sp_224,
40	blake2sp_224_context,
41	blake2sp_256,
42	blake2sp_256_context,
43	blake2b_160,
44	blake2b_160_context,
45	blake2b_224,
46	blake2b_224_context,
47	blake2b_256,
48	blake2b_256_context,
49	blake2b_384,
50	blake2b_384_context,
51	blake2b_512,
52	blake2b_512_context,
53	blake2bp_512,
54	blake2bp_512_context,
55	md5,
56	md5_context,
57	md5s,
58	hashUpdate,
59	hashFinalize,
60	Digest,
61	HashAlgorithm,
62	Context,
63	props_hashes_stable,
64	Mac(..),
65	calcMac,
66	props_macs_stable,
67	IncrementalVerifier(..),
68	mkIncrementalVerifier,
69) where
70
71import qualified Data.ByteString as S
72import qualified Data.ByteString.Lazy as L
73import qualified Data.Text as T
74import qualified Data.Text.Encoding as T
75import Data.IORef
76import "cryptonite" Crypto.MAC.HMAC hiding (Context)
77import "cryptonite" Crypto.Hash
78
79sha1 :: L.ByteString -> Digest SHA1
80sha1 = hashlazy
81
82sha1_context :: Context SHA1
83sha1_context = hashInit
84
85sha2_224 :: L.ByteString -> Digest SHA224
86sha2_224 = hashlazy
87
88sha2_224_context :: Context SHA224
89sha2_224_context = hashInit
90
91sha2_256 :: L.ByteString -> Digest SHA256
92sha2_256 = hashlazy
93
94sha2_256_context :: Context SHA256
95sha2_256_context = hashInit
96
97sha2_384 :: L.ByteString -> Digest SHA384
98sha2_384 = hashlazy
99
100sha2_384_context :: Context SHA384
101sha2_384_context = hashInit
102
103sha2_512 :: L.ByteString -> Digest SHA512
104sha2_512 = hashlazy
105
106sha2_512_context :: Context SHA512
107sha2_512_context = hashInit
108
109sha3_224 :: L.ByteString -> Digest SHA3_224
110sha3_224 = hashlazy
111
112sha3_224_context :: Context SHA3_224
113sha3_224_context = hashInit
114
115sha3_256 :: L.ByteString -> Digest SHA3_256
116sha3_256 = hashlazy
117
118sha3_256_context :: Context SHA3_256
119sha3_256_context = hashInit
120
121sha3_384 :: L.ByteString -> Digest SHA3_384
122sha3_384 = hashlazy
123
124sha3_384_context :: Context SHA3_384
125sha3_384_context = hashInit
126
127sha3_512 :: L.ByteString -> Digest SHA3_512
128sha3_512 = hashlazy
129
130sha3_512_context :: Context SHA3_512
131sha3_512_context = hashInit
132
133skein256 :: L.ByteString -> Digest Skein256_256
134skein256 = hashlazy
135
136skein256_context :: Context Skein256_256
137skein256_context = hashInit
138
139skein512 :: L.ByteString -> Digest Skein512_512
140skein512 = hashlazy
141
142skein512_context :: Context Skein512_512
143skein512_context = hashInit
144
145blake2s_160 :: L.ByteString -> Digest Blake2s_160
146blake2s_160 = hashlazy
147
148blake2s_160_context :: Context Blake2s_160
149blake2s_160_context = hashInit
150
151blake2s_224 :: L.ByteString -> Digest Blake2s_224
152blake2s_224 = hashlazy
153
154blake2s_224_context :: Context Blake2s_224
155blake2s_224_context = hashInit
156
157blake2s_256 :: L.ByteString -> Digest Blake2s_256
158blake2s_256 = hashlazy
159
160blake2s_256_context :: Context Blake2s_256
161blake2s_256_context = hashInit
162
163blake2sp_224 :: L.ByteString -> Digest Blake2sp_224
164blake2sp_224 = hashlazy
165
166blake2sp_224_context :: Context Blake2sp_224
167blake2sp_224_context = hashInit
168
169blake2sp_256 :: L.ByteString -> Digest Blake2sp_256
170blake2sp_256 = hashlazy
171
172blake2sp_256_context :: Context Blake2sp_256
173blake2sp_256_context = hashInit
174
175blake2b_160 :: L.ByteString -> Digest Blake2b_160
176blake2b_160 = hashlazy
177
178blake2b_160_context :: Context Blake2b_160
179blake2b_160_context = hashInit
180
181blake2b_224 :: L.ByteString -> Digest Blake2b_224
182blake2b_224 = hashlazy
183
184blake2b_224_context :: Context Blake2b_224
185blake2b_224_context = hashInit
186
187blake2b_256 :: L.ByteString -> Digest Blake2b_256
188blake2b_256 = hashlazy
189
190blake2b_256_context :: Context Blake2b_256
191blake2b_256_context = hashInit
192
193blake2b_384 :: L.ByteString -> Digest Blake2b_384
194blake2b_384 = hashlazy
195
196blake2b_384_context :: Context Blake2b_384
197blake2b_384_context = hashInit
198
199blake2b_512 :: L.ByteString -> Digest Blake2b_512
200blake2b_512 = hashlazy
201
202blake2b_512_context :: Context Blake2b_512
203blake2b_512_context = hashInit
204
205blake2bp_512 :: L.ByteString -> Digest Blake2bp_512
206blake2bp_512 = hashlazy
207
208blake2bp_512_context :: Context Blake2bp_512
209blake2bp_512_context = hashInit
210
211md5 ::  L.ByteString -> Digest MD5
212md5 = hashlazy
213
214md5_context :: Context MD5
215md5_context = hashInit
216
217md5s ::  S.ByteString -> Digest MD5
218md5s = hash
219
220{- Check that all the hashes continue to hash the same. -}
221props_hashes_stable :: [(String, Bool)]
222props_hashes_stable = map (\(desc, hasher, result) -> (desc ++ " stable", hasher foo == result))
223	[ ("sha1", show . sha1, "0beec7b5ea3f0fdbc95d0dd47f3c5bc275da8a33")
224	, ("sha2_224", show . sha2_224, "0808f64e60d58979fcb676c96ec938270dea42445aeefcd3a4e6f8db")
225	, ("sha2_256", show . sha2_256, "2c26b46b68ffc68ff99b453c1d30413413422d706483bfa0f98a5e886266e7ae")
226	, ("sha2_384", show . sha2_384, "98c11ffdfdd540676b1a137cb1a22b2a70350c9a44171d6b1180c6be5cbb2ee3f79d532c8a1dd9ef2e8e08e752a3babb")
227	, ("sha2_512", show . sha2_512, "f7fbba6e0636f890e56fbbf3283e524c6fa3204ae298382d624741d0dc6638326e282c41be5e4254d8820772c5518a2c5a8c0c7f7eda19594a7eb539453e1ed7")
228	, ("skein256", show . skein256, "a04efd9a0aeed6ede40fe5ce0d9361ae7b7d88b524aa19917b9315f1ecf00d33")
229	, ("skein512", show . skein512, "fd8956898113510180aa4658e6c0ac85bd74fb47f4a4ba264a6b705d7a8e8526756e75aecda12cff4f1aca1a4c2830fbf57f458012a66b2b15a3dd7d251690a7")
230	, ("sha3_224", show . sha3_224, "f4f6779e153c391bbd29c95e72b0708e39d9166c7cea51d1f10ef58a")
231	, ("sha3_256", show . sha3_256, "76d3bc41c9f588f7fcd0d5bf4718f8f84b1c41b20882703100b9eb9413807c01")
232	, ("sha3_384", show . sha3_384, "665551928d13b7d84ee02734502b018d896a0fb87eed5adb4c87ba91bbd6489410e11b0fbcc06ed7d0ebad559e5d3bb5")
233	, ("sha3_512", show . sha3_512, "4bca2b137edc580fe50a88983ef860ebaca36c857b1f492839d6d7392452a63c82cbebc68e3b70a2a1480b4bb5d437a7cba6ecf9d89f9ff3ccd14cd6146ea7e7")
234	, ("blake2s_160", show . blake2s_160, "52fb63154f958a5c56864597273ea759e52c6f00")
235	, ("blake2s_224", show . blake2s_224, "9466668503ac415d87b8e1dfd7f348ab273ac1d5e4f774fced5fdb55")
236	, ("blake2s_256", show . blake2s_256, "08d6cad88075de8f192db097573d0e829411cd91eb6ec65e8fc16c017edfdb74")
237	, ("blake2sp_224", show . blake2sp_224, "8492d356fbac99f046f55e114301f7596649cb590e5b083d1a19dcdb")
238	, ("blake2sp_256", show . blake2sp_256, "050dc5786037ea72cb9ed9d0324afcab03c97ec02e8c47368fc5dfb4cf49d8c9")
239	, ("blake2b_160", show . blake2b_160, "983ceba2afea8694cc933336b27b907f90c53a88")
240	, ("blake2b_224", show . blake2b_224, "853986b3fe231d795261b4fb530e1a9188db41e460ec4ca59aafef78")
241	, ("blake2b_256", show . blake2b_256, "b8fe9f7f6255a6fa08f668ab632a8d081ad87983c77cd274e48ce450f0b349fd")
242	, ("blake2b_384", show . blake2b_384, "e629ee880953d32c8877e479e3b4cb0a4c9d5805e2b34c675b5a5863c4ad7d64bb2a9b8257fac9d82d289b3d39eb9cc2")
243	, ("blake2b_512", show . blake2b_512, "ca002330e69d3e6b84a46a56a6533fd79d51d97a3bb7cad6c2ff43b354185d6dc1e723fb3db4ae0737e120378424c714bb982d9dc5bbd7a0ab318240ddd18f8d")
244	, ("blake2bp_512", show . blake2bp_512, "8ca9ccee7946afcb686fe7556628b5ba1bf9a691da37ca58cd049354d99f37042c007427e5f219b9ab5063707ec6823872dee413ee014b4d02f2ebb6abb5f643")
245	, ("md5", show . md5, "acbd18db4cc2f85cedef654fccc4a4d8")
246	]
247  where
248	foo = L.fromChunks [T.encodeUtf8 $ T.pack "foo"]
249
250data Mac = HmacSha1 | HmacSha224 | HmacSha256 | HmacSha384 | HmacSha512
251	deriving (Eq)
252
253calcMac
254	:: Mac          -- ^ MAC
255	-> S.ByteString -- ^ secret key
256	-> S.ByteString -- ^ message
257	-> String       -- ^ MAC'ed message, in hexadecimal
258calcMac mac = case mac of
259	HmacSha1   -> use SHA1
260	HmacSha224 -> use SHA224
261	HmacSha256 -> use SHA256
262	HmacSha384 -> use SHA384
263	HmacSha512 -> use SHA512
264  where
265	use alg k m = show (hmacGetDigest (hmacWitnessAlg alg k m))
266
267	hmacWitnessAlg :: HashAlgorithm a => a -> S.ByteString -> S.ByteString -> HMAC a
268	hmacWitnessAlg _ = hmac
269
270-- Check that all the MACs continue to produce the same.
271props_macs_stable :: [(String, Bool)]
272props_macs_stable = map (\(desc, mac, result) -> (desc ++ " stable", calcMac mac key msg == result))
273	[ ("HmacSha1", HmacSha1, "46b4ec586117154dacd49d664e5d63fdc88efb51")
274	, ("HmacSha224", HmacSha224, "4c1f774863acb63b7f6e9daa9b5c543fa0d5eccf61e3ffc3698eacdd")
275	, ("HmacSha256", HmacSha256, "f9320baf0249169e73850cd6156ded0106e2bb6ad8cab01b7bbbebe6d1065317")
276	, ("HmacSha384", HmacSha384, "3d10d391bee2364df2c55cf605759373e1b5a4ca9355d8f3fe42970471eca2e422a79271a0e857a69923839015877fc6")
277	, ("HmacSha512", HmacSha512, "114682914c5d017dfe59fdc804118b56a3a652a0b8870759cf9e792ed7426b08197076bf7d01640b1b0684df79e4b67e37485669e8ce98dbab60445f0db94fce")
278	]
279  where
280	key = T.encodeUtf8 $ T.pack "foo"
281	msg = T.encodeUtf8 $ T.pack "bar"
282
283data IncrementalVerifier = IncrementalVerifier
284	{ updateIncremental :: S.ByteString -> IO ()
285	-- ^ Called repeatedly on each peice of the content.
286	, finalizeIncremental :: IO (Maybe Bool)
287	-- ^ Called once the full content has been sent, returns True
288	-- if the hash verified, False if it did not, and Nothing if
289	-- incremental verification was unable to be done.
290	, unableIncremental :: IO ()
291	-- ^ Call if the incremental verification is unable to be done.
292	, positionIncremental :: IO (Maybe Integer)
293	-- ^ Returns the number of bytes that have been fed to this
294	-- incremental verifier so far. (Nothing if unableIncremental was
295	-- called.)
296	, descVerify :: String
297	-- ^ A description of what is done to verify the content.
298	}
299
300mkIncrementalVerifier :: HashAlgorithm h => Context h -> String -> (String -> Bool) -> IO IncrementalVerifier
301mkIncrementalVerifier ctx descverify samechecksum = do
302	v <- newIORef (Just (ctx, 0))
303	return $ IncrementalVerifier
304		{ updateIncremental = \b ->
305			modifyIORef' v $ \case
306				(Just (ctx', n)) ->
307					let !ctx'' = hashUpdate ctx' b
308					    !n' = n + fromIntegral (S.length b)
309					in (Just (ctx'', n'))
310				Nothing -> Nothing
311		, finalizeIncremental =
312			readIORef v >>= \case
313				(Just (ctx', _)) -> do
314					let digest = hashFinalize ctx'
315					return $ Just $
316						samechecksum (show digest)
317				Nothing -> return Nothing
318		, unableIncremental = writeIORef v Nothing
319		, positionIncremental = readIORef v >>= \case
320			Just (_, n) -> return (Just n)
321			Nothing -> return Nothing
322		, descVerify = descverify
323		}
324