@@ -45,7 +45,6 @@ import Data.Word
45
45
import Foreign.Storable
46
46
import Foreign.Ptr
47
47
import Foreign.ForeignPtr
48
- import System.IO
49
48
import Data.Binary
50
49
import Data.Binary.Get
51
50
import Data.Binary.Put
@@ -93,11 +92,10 @@ md5 = hash
93
92
md5Finalize :: MD5Context -> B. ByteString -> MD5Digest
94
93
md5Finalize ! ctx@ (MD5Ctx par@ (MD5Par a b c d) ! totLen) end =
95
94
let totLen' = 8 * (totLen + fromIntegral l) :: Word64
96
- padBS = P. runPut ( do
97
- P. putByteString end
98
- P. putWord8 0x80
99
- mapM_ P. putWord8 (replicate lenZeroPad 0 )
100
- P. putWord64le totLen' )
95
+ padBS = P. runPut $ do P. putByteString end
96
+ P. putWord8 0x80
97
+ mapM_ P. putWord8 (replicate lenZeroPad 0 )
98
+ P. putWord64le totLen'
101
99
in MD5Digest $ blockAndDo par padBS
102
100
where
103
101
l = B. length end
@@ -112,20 +110,20 @@ md5Finalize !ctx@(MD5Ctx par@(MD5Par a b c d) !totLen) end =
112
110
md5Update :: MD5Context -> B. ByteString -> MD5Context
113
111
md5Update ctx bs
114
112
| B. length bs `rem` blockSizeBytes /= 0 = error " Invalid use of hash update routine (see crypto-api Hash class semantics)"
115
- | otherwise =
113
+ | otherwise =
116
114
let bs' = if isAligned bs then bs else B. copy bs -- copying has been measured as a net win on my x86 system
117
115
new = blockAndDo (mdPartial ctx) bs'
118
116
in ctx { mdPartial = new, mdTotalLen = mdTotalLen ctx + fromIntegral (B. length bs) }
119
117
120
118
blockAndDo :: MD5Partial -> B. ByteString -> MD5Partial
121
119
blockAndDo ! ctx bs
122
120
| B. length bs == 0 = ctx
123
- | otherwise =
121
+ | otherwise =
124
122
let ! new = performMD5Update ctx bs
125
123
in blockAndDo new (unsafeDrop blockSizeBytes bs)
126
124
{-# INLINE blockAndDo #-}
127
125
128
- -- Assumes ByteString length == blockSizeBytes, will fold the
126
+ -- Assumes ByteString length == blockSizeBytes, will fold the
129
127
-- context across calls to applyMD5Rounds.
130
128
performMD5Update :: MD5Partial -> B. ByteString -> MD5Partial
131
129
performMD5Update ! par@ (MD5Par ! a ! b ! c ! d) ! bs =
@@ -259,7 +257,7 @@ instance Show MD5Digest where
259
257
show (MD5Digest h) = show h
260
258
261
259
instance Show MD5Partial where
262
- show (MD5Par a b c d) =
260
+ show (MD5Par a b c d) =
263
261
let bs = runPut $ putWord32be d >> putWord32be c >> putWord32be b >> putWord32be a
264
262
in foldl' (\ str w -> let c = showHex w str
265
263
in if length c < length str + 2
@@ -301,11 +299,11 @@ instance S.Serialize MD5Context where
301
299
302
300
instance S. Serialize MD5Partial where
303
301
put (MD5Par a b c d) = P. putWord32le a >> P. putWord32le b >> P. putWord32le c >> P. putWord32le d
304
- get = do a <- G. getWord32le
305
- b <- G. getWord32le
306
- c <- G. getWord32le
307
- d <- G. getWord32le
308
- return $ MD5Par a b c 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)))))
309
307
310
308
instance Hash MD5Context MD5Digest where
311
309
outputLength = Tagged 128
0 commit comments