{-# LANGUAGE OverloadedStrings #-}
module Data.Git.Hash where
import qualified Crypto.Hash.SHA1 as Sha1
import qualified Data.ByteString as B
import qualified Data.ByteString.Base16 as B16
import qualified Data.ByteString.Lazy as BL
import Data.String
newtype Sha1 = Sha1 { getSha1 :: B.ByteString }
deriving (Eq, Ord, Show)
validSha1 :: Sha1 -> Bool
validSha1 (Sha1 s) = B.length s == 20
newtype Sha1Hex = Sha1Hex { getSha1Hex :: B.ByteString }
deriving (Eq, Ord, Show)
validSha1Hex :: Sha1Hex -> Bool
validSha1Hex (Sha1Hex s) = B.length s == 40 && B.all (`B.elem` "0123456789abcdef") s
class HasSha1 a where
sha1 :: a -> Sha1
instance HasSha1 B.ByteString where
sha1 = Sha1 . Sha1.hash
instance HasSha1 BL.ByteString where
sha1 = Sha1 . Sha1.hashlazy
instance IsString Sha1Hex where
fromString = Sha1Hex . fromString
sha1hex :: HasSha1 a => a -> Sha1Hex
sha1hex = toHex . sha1
fromHex :: Sha1Hex -> Sha1
fromHex = Sha1 . go . B16.decode . getSha1Hex
where go (h, "") = h
go (_, rest) = error $ "invalid hex: " ++ show rest
toHex :: Sha1 -> Sha1Hex
toHex = Sha1Hex . B16.encode . getSha1