Skip to content

Commit a10ee3f

Browse files
author
Thomas M. DuBuisson
committed
House cleaning
1 parent b8d60d4 commit a10ee3f

File tree

1 file changed

+17
-20
lines changed

1 file changed

+17
-20
lines changed

Data/Digest/Pure/MD5.hs

Lines changed: 17 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -33,35 +33,32 @@ module Data.Digest.Pure.MD5
3333
, Hash(..)
3434
) where
3535

36-
import Data.ByteString.Unsafe (unsafeUseAsCString)
3736
import qualified Data.ByteString as B
3837
import qualified Data.ByteString.Lazy as L
39-
import Data.ByteString.Unsafe (unsafeDrop)
38+
import Data.ByteString.Unsafe (unsafeDrop,unsafeUseAsCString)
4039
import Data.ByteString.Internal
4140
import Data.Bits
4241
import Data.List
43-
import Data.Int (Int64)
4442
import Data.Word
4543
import Foreign.Storable
46-
import Foreign.Ptr
47-
import Foreign.ForeignPtr
44+
import Foreign.Ptr (castPtr)
4845
import Data.Binary
4946
import Data.Binary.Get
5047
import Data.Binary.Put
5148
import qualified Data.Serialize.Get as G
5249
import qualified Data.Serialize.Put as P
5350
import qualified Data.Serialize as S
5451
import Crypto.Classes (Hash(..), hash)
52+
import Control.Monad (replicateM_)
5553
import Data.Tagged
5654
import Numeric
5755

5856
-- | Block size in bits
5957
md5BlockSize :: Int
6058
md5BlockSize = 512
6159

60+
blockSizeBytes :: Int
6261
blockSizeBytes = md5BlockSize `div` 8
63-
blockSizeBytesI64 = (fromIntegral blockSizeBytes) :: Int64
64-
blockSizeBits = (fromIntegral md5BlockSize) :: Word64
6562

6663
-- | The type for intermediate results (from md5Update)
6764
data MD5Partial = MD5Par {-# UNPACK #-} !Word32 {-# UNPACK #-} !Word32 {-# UNPACK #-} !Word32 {-# UNPACK #-} !Word32
@@ -78,6 +75,8 @@ data MD5Digest = MD5Digest MD5Partial deriving (Eq, Ord)
7875
-- | The initial context to use when calling md5Update for the first time
7976
md5InitialContext :: MD5Context
8077
md5InitialContext = MD5Ctx (MD5Par h0 h1 h2 h3) 0
78+
79+
h0,h1,h2,h3 :: Word32
8180
h0 = 0x67452301
8281
h1 = 0xEFCDAB89
8382
h2 = 0x98BADCFE
@@ -90,11 +89,11 @@ md5 = hash
9089

9190
-- | Closes an MD5 context, thus producing the digest.
9291
md5Finalize :: MD5Context -> B.ByteString -> MD5Digest
93-
md5Finalize !ctx@(MD5Ctx par@(MD5Par a b c d) !totLen) end =
92+
md5Finalize (MD5Ctx par !totLen) end =
9493
let totLen' = 8*(totLen + fromIntegral l) :: Word64
9594
padBS = P.runPut $ do P.putByteString end
9695
P.putWord8 0x80
97-
mapM_ P.putWord8 (replicate lenZeroPad 0)
96+
replicateM_ lenZeroPad (P.putWord8 0)
9897
P.putWord64le totLen'
9998
in MD5Digest $ blockAndDo par padBS
10099
where
@@ -126,15 +125,16 @@ blockAndDo !ctx bs
126125
-- Assumes ByteString length == blockSizeBytes, will fold the
127126
-- context across calls to applyMD5Rounds.
128127
performMD5Update :: MD5Partial -> B.ByteString -> MD5Partial
129-
performMD5Update !par@(MD5Par !a !b !c !d) !bs =
128+
performMD5Update par@(MD5Par !a !b !c !d) !bs =
130129
let MD5Par a' b' c' d' = applyMD5Rounds par bs
131130
in MD5Par (a' + a) (b' + b) (c' + c) (d' + d)
132131
{-# INLINE performMD5Update #-}
133132

133+
isAligned :: ByteString -> Bool
134134
isAligned (PS _ off _) = off `rem` 4 == 0
135135

136136
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" #-}
138138
let -- Round 1
139139
!r0 = ff a b c d (w!!0) 7 3614090360
140140
!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 ::
247247
#endif
248248
{-# INLINE getNthWord #-}
249249

250-
infix 9 .<.
251-
(.<.) :: Word8 -> Int -> Word32
252-
(.<.) w i = (fromIntegral w) `shiftL` i
253-
254250
----- Some quick and dirty instances follow -----
255251

256252
instance Show MD5Digest where
257253
show (MD5Digest h) = show h
258254

259255
instance Show MD5Partial where
260256
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)
266263

267264
instance Binary MD5Digest where
268265
put (MD5Digest p) = put p

0 commit comments

Comments
 (0)