{-# LANGUAGE OverloadedStrings #-}

-- | Pretty much everything in git works by SHA1 hashes.  The 'Sha1' type represents a 20-byte
-- "binary" hash.  The 'Sha1Hex' type is for the 40-byte hex representation of a hash.

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

-- | A 20-byte "binary" SHA1 hash.
newtype Sha1 = Sha1 { getSha1 :: B.ByteString }
    deriving (Eq, Ord, Show)

-- | Ensure a 'Sha1' is valid (that is, is 20 bytes long).
validSha1 :: Sha1 -> Bool
validSha1 (Sha1 s) = B.length s == 20

-- | A 40-byte hex representation of a SHA1 hash.
newtype Sha1Hex = Sha1Hex { getSha1Hex :: B.ByteString }
    deriving (Eq, Ord, Show)

-- | Ensure a 'Sha1Hex' is valid (that is, is 40 bytes long and consists only of hex characters).
validSha1Hex :: Sha1Hex -> Bool
validSha1Hex (Sha1Hex s) = B.length s == 40 && B.all (`B.elem` "0123456789abcdef") s

-- | A @Hashable@-alike for 'Sha1's.
class HasSha1 a where
    sha1 :: a -> Sha1

-- | Direct SHA1 of a bytestring.
instance HasSha1 B.ByteString where
    sha1 = Sha1 . Sha1.hash

-- | Direct SHA1 of a lazy bytestring.
instance HasSha1 BL.ByteString where
    sha1 = Sha1 . Sha1.hashlazy

-- | This isn't checked; buyer beware.
instance IsString Sha1Hex where
    fromString = Sha1Hex . fromString

-- | Hash something to a 'Sha1Hex'
sha1hex :: HasSha1 a => a -> Sha1Hex
sha1hex = toHex . sha1

-- | Convert a 'Sha1Hex' into a 'Sha1'
fromHex :: Sha1Hex -> Sha1
fromHex = Sha1 . go . B16.decode . getSha1Hex
    where go (h, "")   = h
          go (_, rest) = error $ "invalid hex: " ++ show rest

-- | Convert a 'Sha1' to a 'Sha1Hex'
toHex :: Sha1 -> Sha1Hex
toHex = Sha1Hex . B16.encode . getSha1