{-# LANGUAGE DeriveDataTypeable #-}
module Data.Git.Ref
( Ref
, SHA1
, Crypto.Hash.HashAlgorithm
, Crypto.Hash.hashDigestSize
, RefInvalid(..)
, RefNotFound(..)
, isHex
, isHexString
, fromHex
, fromHexString
, fromBinary
, fromDigest
, toBinary
, toHex
, toHexString
, refPrefix
, cmpPrefix
, toFilePathParts
, hash
, hashLBS
, hashAlg
, hashAlgFromRef
) where
import qualified Crypto.Hash
import Crypto.Hash (Digest, SHA1, digestFromByteString)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Unsafe as B (unsafeIndex)
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Char8 as BC
import Data.ByteArray.Encoding
import qualified Data.ByteArray as B (convert)
import Data.Char (isHexDigit)
import Data.Data
import Control.Exception (Exception, throw)
newtype Ref hash = Ref (Digest hash)
deriving (Eq,Ord,Typeable)
instance Show (Ref hash) where
show = BC.unpack . toHex
data RefInvalid = RefInvalid ByteString
deriving (Show,Eq,Data,Typeable)
data RefNotFound hash = RefNotFound (Ref hash)
deriving (Show,Eq,Typeable)
instance Exception RefInvalid
instance Typeable hash => Exception (RefNotFound hash)
isHex :: ByteString -> Bool
isHex = and . map isHexDigit . BC.unpack
isHexString :: String -> Bool
isHexString = and . map isHexDigit
fromHex :: Crypto.Hash.HashAlgorithm hash => ByteString -> Ref hash
fromHex s =
case either (const Nothing) Just (convertFromBase Base16 s :: Either String ByteString) >>= digestFromByteString of
Nothing -> throw $ RefInvalid s
Just hsh -> Ref hsh
fromHexString :: Crypto.Hash.HashAlgorithm hash => String -> Ref hash
fromHexString = fromHex . BC.pack
toHex :: Ref hash -> ByteString
toHex (Ref bs) = convertToBase Base16 bs
toHexString :: Ref hash -> String
toHexString (Ref d) = show d
fromBinary :: Crypto.Hash.HashAlgorithm hash => ByteString -> Ref hash
fromBinary b = maybe (throw $ RefInvalid b) Ref $ digestFromByteString b
fromDigest :: Crypto.Hash.HashAlgorithm hash => Digest hash -> Ref hash
fromDigest = Ref
toBinary :: Ref hash -> ByteString
toBinary (Ref b) = B.convert b
refPrefix :: Ref hash -> Int
refPrefix (Ref b) = fromIntegral $ B.unsafeIndex (B.convert b) 0
cmpPrefix :: String -> Ref hash -> Ordering
cmpPrefix pre ref = pre `compare` (take (length pre) $ toHexString ref)
toFilePathParts :: Ref hash -> (String, String)
toFilePathParts ref = splitAt 2 $ show ref
hash :: Crypto.Hash.HashAlgorithm hash => ByteString -> Ref hash
hash = Ref . Crypto.Hash.hash
hashLBS :: Crypto.Hash.HashAlgorithm hash => L.ByteString -> Ref hash
hashLBS = Ref . Crypto.Hash.hashlazy
hashAlg :: Crypto.Hash.HashAlgorithm hash => hash
hashAlg = error "polymorphic hash algorithm. only to use with hashDigestSize"
hashAlgFromRef :: Crypto.Hash.HashAlgorithm hash => Ref hash -> hash
hashAlgFromRef _ = hashAlg