19
19
-----------------------------------------------------------------------------
20
20
21
21
module Data.Digest.Pure.MD5
22
- (
22
+ (
23
23
-- * Types
24
24
MD5Context
25
25
, MD5Digest
@@ -29,8 +29,8 @@ module Data.Digest.Pure.MD5
29
29
, md5
30
30
, md5Update
31
31
, md5Finalize
32
- -- * Crypto-API interface
33
- , Hash (.. )
32
+ -- * Crypto-API interface
33
+ , Hash (.. )
34
34
) where
35
35
36
36
import Data.ByteString.Unsafe (unsafeUseAsCString )
@@ -111,24 +111,24 @@ md5Update :: MD5Context -> B.ByteString -> MD5Context
111
111
md5Update ctx bs
112
112
| B. length bs `rem` blockSizeBytes /= 0 = error " Invalid use of hash update routine (see crypto-api Hash class semantics)"
113
113
| otherwise =
114
- let bs' = if isAligned bs then bs else B. copy bs -- copying has been measured as a net win on my x86 system
115
- new = blockAndDo (mdPartial ctx) bs'
116
- in ctx { mdPartial = new, mdTotalLen = mdTotalLen ctx + fromIntegral (B. length bs) }
114
+ let bs' = if isAligned bs then bs else B. copy bs -- copying has been measured as a net win on my x86 system
115
+ new = blockAndDo (mdPartial ctx) bs'
116
+ in ctx { mdPartial = new, mdTotalLen = mdTotalLen ctx + fromIntegral (B. length bs) }
117
117
118
118
blockAndDo :: MD5Partial -> B. ByteString -> MD5Partial
119
119
blockAndDo ! ctx bs
120
120
| B. length bs == 0 = ctx
121
121
| otherwise =
122
- let ! new = performMD5Update ctx bs
123
- in blockAndDo new (unsafeDrop blockSizeBytes bs)
122
+ let ! new = performMD5Update ctx bs
123
+ in blockAndDo new (unsafeDrop blockSizeBytes bs)
124
124
{-# INLINE blockAndDo #-}
125
125
126
126
-- Assumes ByteString length == blockSizeBytes, will fold the
127
127
-- context across calls to applyMD5Rounds.
128
128
performMD5Update :: MD5Partial -> B. ByteString -> MD5Partial
129
129
performMD5Update ! par@ (MD5Par ! a ! b ! c ! d) ! bs =
130
130
let MD5Par a' b' c' d' = applyMD5Rounds par bs
131
- in MD5Par (a' + a) (b' + b) (c' + c) (d' + d)
131
+ in MD5Par (a' + a) (b' + b) (c' + c) (d' + d)
132
132
{-# INLINE performMD5Update #-}
133
133
134
134
isAligned (PS _ off _) = off `rem` 4 == 0
@@ -298,16 +298,21 @@ instance S.Serialize MD5Context where
298
298
return $ MD5Ctx p l
299
299
300
300
instance S. Serialize MD5Partial where
301
- put (MD5Par a b c d) = P. putWord32le a >> P. putWord32le b >> P. putWord32le c >> P. putWord32le d
302
- get = G. getWord32le >>= (\ a ->
303
- G. getWord32le >>= (\ b ->
304
- G. getWord32le >>= (\ c ->
305
- G. getWord32le >>= (\ d ->
306
- return (MD5Par a b c d)))))
301
+ put (MD5Par a b c d) = do
302
+ P. putWord32le a
303
+ P. putWord32le b
304
+ P. putWord32le c
305
+ P. putWord32le d
306
+ get = do
307
+ a <- G. getWord32le
308
+ b <- G. getWord32le
309
+ c <- G. getWord32le
310
+ d <- G. getWord32le
311
+ return (MD5Par a b c d)
307
312
308
313
instance Hash MD5Context MD5Digest where
309
- outputLength = Tagged 128
310
- blockLength = Tagged 512
311
- initialCtx = md5InitialContext
312
- updateCtx = md5Update
313
- finalize = md5Finalize
314
+ outputLength = Tagged 128
315
+ blockLength = Tagged 512
316
+ initialCtx = md5InitialContext
317
+ updateCtx = md5Update
318
+ finalize = md5Finalize
0 commit comments