License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | unix |
Safe Haskell | None |
Language | Haskell98 |
Synopsis
- data Ref hash
- data SHA1
- class HashAlgorithm a
- hashDigestSize :: HashAlgorithm a => a -> Int
- data RefInvalid = RefInvalid ByteString
- data RefNotFound hash = RefNotFound (Ref hash)
- isHex :: ByteString -> Bool
- isHexString :: String -> Bool
- fromHex :: HashAlgorithm hash => ByteString -> Ref hash
- fromHexString :: HashAlgorithm hash => String -> Ref hash
- fromBinary :: HashAlgorithm hash => ByteString -> Ref hash
- fromDigest :: HashAlgorithm hash => Digest hash -> Ref hash
- toBinary :: Ref hash -> ByteString
- toHex :: Ref hash -> ByteString
- toHexString :: Ref hash -> String
- refPrefix :: Ref hash -> Int
- cmpPrefix :: String -> Ref hash -> Ordering
- toFilePathParts :: Ref hash -> (String, String)
- hash :: HashAlgorithm hash => ByteString -> Ref hash
- hashLBS :: HashAlgorithm hash => ByteString -> Ref hash
- hashAlg :: HashAlgorithm hash => hash
- hashAlgFromRef :: HashAlgorithm hash => Ref hash -> hash
Documentation
represent a git reference (SHA1)
SHA1 cryptographic hash algorithm
Instances
Data SHA1 | |
Defined in Crypto.Hash.SHA1 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA1 -> c SHA1 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA1 # dataTypeOf :: SHA1 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA1) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA1) # gmapT :: (forall b. Data b => b -> b) -> SHA1 -> SHA1 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA1 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA1 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA1 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA1 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA1 -> m SHA1 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA1 -> m SHA1 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA1 -> m SHA1 # | |
Show SHA1 | |
HashAlgorithm SHA1 | |
Defined in Crypto.Hash.SHA1 type HashBlockSize SHA1 :: Nat # type HashDigestSize SHA1 :: Nat # type HashInternalContextSize SHA1 :: Nat # | |
Resolvable (Ref SHA1) Source # | |
type HashInternalContextSize SHA1 | |
Defined in Crypto.Hash.SHA1 | |
type HashDigestSize SHA1 | |
Defined in Crypto.Hash.SHA1 | |
type HashBlockSize SHA1 | |
Defined in Crypto.Hash.SHA1 |
class HashAlgorithm a #
Class representing hashing algorithms.
The interface presented here is update in place and lowlevel. the Hash module takes care of hidding the mutable interface properly.
hashBlockSize, hashDigestSize, hashInternalContextSize, hashInternalInit, hashInternalUpdate, hashInternalFinalize
Instances
hashDigestSize :: HashAlgorithm a => a -> Int #
Get the digest size of a hash algorithm
Exceptions
data RefInvalid Source #
Invalid Reference exception raised when using something that is not a ref as a ref.
Instances
Eq RefInvalid Source # | |
Defined in Data.Git.Ref (==) :: RefInvalid -> RefInvalid -> Bool # (/=) :: RefInvalid -> RefInvalid -> Bool # | |
Data RefInvalid Source # | |
Defined in Data.Git.Ref gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RefInvalid -> c RefInvalid # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RefInvalid # toConstr :: RefInvalid -> Constr # dataTypeOf :: RefInvalid -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RefInvalid) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RefInvalid) # gmapT :: (forall b. Data b => b -> b) -> RefInvalid -> RefInvalid # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RefInvalid -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RefInvalid -> r # gmapQ :: (forall d. Data d => d -> u) -> RefInvalid -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RefInvalid -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RefInvalid -> m RefInvalid # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RefInvalid -> m RefInvalid # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RefInvalid -> m RefInvalid # | |
Show RefInvalid Source # | |
Defined in Data.Git.Ref showsPrec :: Int -> RefInvalid -> ShowS # show :: RefInvalid -> String # showList :: [RefInvalid] -> ShowS # | |
Exception RefInvalid Source # | |
Defined in Data.Git.Ref toException :: RefInvalid -> SomeException # fromException :: SomeException -> Maybe RefInvalid # displayException :: RefInvalid -> String # |
data RefNotFound hash Source #
Reference wasn't found
RefNotFound (Ref hash) |
Instances
Eq (RefNotFound hash) Source # | |
Defined in Data.Git.Ref (==) :: RefNotFound hash -> RefNotFound hash -> Bool # (/=) :: RefNotFound hash -> RefNotFound hash -> Bool # | |
Show (RefNotFound hash) Source # | |
Defined in Data.Git.Ref showsPrec :: Int -> RefNotFound hash -> ShowS # show :: RefNotFound hash -> String # showList :: [RefNotFound hash] -> ShowS # | |
Typeable hash => Exception (RefNotFound hash) Source # | |
Defined in Data.Git.Ref toException :: RefNotFound hash -> SomeException # fromException :: SomeException -> Maybe (RefNotFound hash) # displayException :: RefNotFound hash -> String # |
convert from bytestring and string
isHex :: ByteString -> Bool Source #
isHexString :: String -> Bool Source #
fromHex :: HashAlgorithm hash => ByteString -> Ref hash Source #
take a hexadecimal bytestring that represent a reference and turn into a ref
fromHexString :: HashAlgorithm hash => String -> Ref hash Source #
take a hexadecimal string that represent a reference and turn into a ref
fromBinary :: HashAlgorithm hash => ByteString -> Ref hash Source #
transform a bytestring that represent a binary bytestring and returns a ref.
fromDigest :: HashAlgorithm hash => Digest hash -> Ref hash Source #
transform a bytestring that represent a binary bytestring and returns a ref.
toBinary :: Ref hash -> ByteString Source #
turn a reference into a binary bytestring
toHex :: Ref hash -> ByteString Source #
transform a ref into an hexadecimal bytestring
toHexString :: Ref hash -> String Source #
transform a ref into an hexadecimal string
Misc function related to ref
toFilePathParts :: Ref hash -> (String, String) Source #
returns the splitted format "prefix/suffix" for addressing the loose object database
Hash ByteString types to a ref
hash :: HashAlgorithm hash => ByteString -> Ref hash Source #
hash a bytestring into a reference
hashLBS :: HashAlgorithm hash => ByteString -> Ref hash Source #
hash a lazy bytestring into a reference
hashAlg :: HashAlgorithm hash => hash Source #
Any hash algorithm
hashAlgFromRef :: HashAlgorithm hash => Ref hash -> hash Source #