@@ -33,35 +33,32 @@ module Data.Digest.Pure.MD5
33
33
, Hash (.. )
34
34
) where
35
35
36
- import Data.ByteString.Unsafe (unsafeUseAsCString )
37
36
import qualified Data.ByteString as B
38
37
import qualified Data.ByteString.Lazy as L
39
- import Data.ByteString.Unsafe (unsafeDrop )
38
+ import Data.ByteString.Unsafe (unsafeDrop , unsafeUseAsCString )
40
39
import Data.ByteString.Internal
41
40
import Data.Bits
42
41
import Data.List
43
- import Data.Int (Int64 )
44
42
import Data.Word
45
43
import Foreign.Storable
46
- import Foreign.Ptr
47
- import Foreign.ForeignPtr
44
+ import Foreign.Ptr (castPtr )
48
45
import Data.Binary
49
46
import Data.Binary.Get
50
47
import Data.Binary.Put
51
48
import qualified Data.Serialize.Get as G
52
49
import qualified Data.Serialize.Put as P
53
50
import qualified Data.Serialize as S
54
51
import Crypto.Classes (Hash (.. ), hash )
52
+ import Control.Monad (replicateM_ )
55
53
import Data.Tagged
56
54
import Numeric
57
55
58
56
-- | Block size in bits
59
57
md5BlockSize :: Int
60
58
md5BlockSize = 512
61
59
60
+ blockSizeBytes :: Int
62
61
blockSizeBytes = md5BlockSize `div` 8
63
- blockSizeBytesI64 = (fromIntegral blockSizeBytes) :: Int64
64
- blockSizeBits = (fromIntegral md5BlockSize) :: Word64
65
62
66
63
-- | The type for intermediate results (from md5Update)
67
64
data MD5Partial = MD5Par {- # UNPACK #-} !Word32 {- # UNPACK #-} !Word32 {- # UNPACK #-} !Word32 {- # UNPACK #-} !Word32
@@ -78,6 +75,8 @@ data MD5Digest = MD5Digest MD5Partial deriving (Eq, Ord)
78
75
-- | The initial context to use when calling md5Update for the first time
79
76
md5InitialContext :: MD5Context
80
77
md5InitialContext = MD5Ctx (MD5Par h0 h1 h2 h3) 0
78
+
79
+ h0 ,h1 ,h2 ,h3 :: Word32
81
80
h0 = 0x67452301
82
81
h1 = 0xEFCDAB89
83
82
h2 = 0x98BADCFE
@@ -90,11 +89,11 @@ md5 = hash
90
89
91
90
-- | Closes an MD5 context, thus producing the digest.
92
91
md5Finalize :: MD5Context -> B. ByteString -> MD5Digest
93
- md5Finalize ! ctx @ (MD5Ctx par@ ( MD5Par a b c d) ! totLen) end =
92
+ md5Finalize (MD5Ctx par ! totLen) end =
94
93
let totLen' = 8 * (totLen + fromIntegral l) :: Word64
95
94
padBS = P. runPut $ do P. putByteString end
96
95
P. putWord8 0x80
97
- mapM_ P. putWord8 ( replicate lenZeroPad 0 )
96
+ replicateM_ lenZeroPad ( P. putWord8 0 )
98
97
P. putWord64le totLen'
99
98
in MD5Digest $ blockAndDo par padBS
100
99
where
@@ -126,15 +125,16 @@ blockAndDo !ctx bs
126
125
-- Assumes ByteString length == blockSizeBytes, will fold the
127
126
-- context across calls to applyMD5Rounds.
128
127
performMD5Update :: MD5Partial -> B. ByteString -> MD5Partial
129
- performMD5Update ! par@ (MD5Par ! a ! b ! c ! d) ! bs =
128
+ performMD5Update par@ (MD5Par ! a ! b ! c ! d) ! bs =
130
129
let MD5Par a' b' c' d' = applyMD5Rounds par bs
131
130
in MD5Par (a' + a) (b' + b) (c' + c) (d' + d)
132
131
{-# INLINE performMD5Update #-}
133
132
133
+ isAligned :: ByteString -> Bool
134
134
isAligned (PS _ off _) = off `rem` 4 == 0
135
135
136
136
applyMD5Rounds :: MD5Partial -> ByteString -> MD5Partial
137
- applyMD5Rounds par @ (MD5Par a b c d) w = {-# SCC "applyMD5Rounds" #-}
137
+ applyMD5Rounds (MD5Par a b c d) w = {-# SCC "applyMD5Rounds" #-}
138
138
let -- Round 1
139
139
! r0 = ff a b c d (w!! 0 ) 7 3614090360
140
140
! r1 = ff d r0 b c (w!! 1 ) 12 3905402710
@@ -247,22 +247,19 @@ getNthWord n = right . G.runGet G.getWord32le . B.drop (n * sizeOf (undefined ::
247
247
#endif
248
248
{-# INLINE getNthWord #-}
249
249
250
- infix 9 .<.
251
- (.<.) :: Word8 -> Int -> Word32
252
- (.<.) w i = (fromIntegral w) `shiftL` i
253
-
254
250
----- Some quick and dirty instances follow -----
255
251
256
252
instance Show MD5Digest where
257
253
show (MD5Digest h) = show h
258
254
259
255
instance Show MD5Partial where
260
256
show (MD5Par a b c d) =
261
- let bs = runPut $ putWord32be d >> putWord32be c >> putWord32be b >> putWord32be a
262
- in foldl' (\ str w -> let c = showHex w str
263
- in if length c < length str + 2
264
- then ' 0' : c
265
- else c) " " (L. unpack bs)
257
+ let bs = runPut $ putWord32be d >> putWord32be c >>
258
+ putWord32be b >> putWord32be a
259
+ in foldl' (\ str w -> let cx = showHex w str
260
+ in if length cx < length str + 2
261
+ then ' 0' : cx
262
+ else cx) " " (L. unpack bs)
266
263
267
264
instance Binary MD5Digest where
268
265
put (MD5Digest p) = put p
0 commit comments