Skip to content

Instantly share code, notes, and snippets.

@joachifm
Created February 28, 2015 15:48
Show Gist options
  • Save joachifm/0add13f048b2b6e73584 to your computer and use it in GitHub Desktop.
Save joachifm/0add13f048b2b6e73584 to your computer and use it in GitHub Desktop.
HashCat
{-|
Hashing the concatenation of two strings leaves a "gap" between the
inputs, so that the hash may be recreated using any two substrings
of the original input:
@
H("banana" <> "split") = H("banan" <> "asplit") = H("b" <> "ananasplit")
@
Hashing the inputs before concatenation removes this gap:
@
H(H("banana") <> H("split")) != H(H("banan" <> H("asplit")))
@
-}
module HashCat (
DigestSum(..),
hashSum,
hashcat,
catDigest,
) where
import qualified Data.Foldable as F
import Data.Monoid (Monoid(..))
import Data.Byteable (toBytes)
import qualified Data.ByteString as SB
import Crypto.Hash (Digest, HashAlgorithm, hash)
------------------------------------------------------------------------
-- A 'Digest' monoid.
-- |
-- Appending two 'DigestSum'S is equivalent to
--
-- @
-- x <> y = H(H(x) <> H(y))
-- @
--
-- where @H@ is the hashing function identified by the @a@ type
-- parameter.
newtype DigestSum a = DigestSum { getDigest :: Digest a }
deriving (Show)
instance (HashAlgorithm a) => Monoid (DigestSum a) where
mempty = DigestSum (hash mempty)
{-# INLINE mempty #-}
x `mappend` y = DigestSum (getDigest x `catDigest` getDigest y)
{-# INLINE mappend #-}
mconcat [] = mempty
mconcat (x:xs) = F.foldl' mappend x xs
{-# INLINE mconcat #-}
-- | A convenient wrapper for constructing 'DigestSum'S.
--
-- @hashSum = DigestSum . hash@
hashSum :: (HashAlgorithm a) => SB.ByteString -> DigestSum a
hashSum = DigestSum . hash
{-# INLINE hashSum #-}
------------------------------------------------------------------------
-- Concatenating hashes.
hashList :: HashAlgorithm a => [SB.ByteString] -> Digest a
hashList = getDigest . mconcat . map (DigestSum . hash)
{-# INLINE hashList #-}
hashcat :: HashAlgorithm a => SB.ByteString -> SB.ByteString -> Digest a
x `hashcat` y = getDigest (hashSum x `mappend` hashSum y)
{-# INLINE hashcat #-}
catDigest :: HashAlgorithm a => Digest a -> Digest a -> Digest a
catDigest x y = hash (toBytes x `SB.append` toBytes y)
{-# INLINE catDigest #-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment