git-0.2.1: Git operations in haskell

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityunix
Safe HaskellNone
LanguageHaskell98

Data.Git.Ref

Contents

Description

 

Synopsis

Documentation

data Ref hash Source #

represent a git reference (SHA1)

Instances

Eq (Ref hash) Source # 

Methods

(==) :: Ref hash -> Ref hash -> Bool #

(/=) :: Ref hash -> Ref hash -> Bool #

Ord (Ref hash) Source # 

Methods

compare :: Ref hash -> Ref hash -> Ordering #

(<) :: Ref hash -> Ref hash -> Bool #

(<=) :: Ref hash -> Ref hash -> Bool #

(>) :: Ref hash -> Ref hash -> Bool #

(>=) :: Ref hash -> Ref hash -> Bool #

max :: Ref hash -> Ref hash -> Ref hash #

min :: Ref hash -> Ref hash -> Ref hash #

Show (Ref hash) Source # 

Methods

showsPrec :: Int -> Ref hash -> ShowS #

show :: Ref hash -> String #

showList :: [Ref hash] -> ShowS #

Resolvable (Ref SHA1) Source # 

Methods

resolve :: GitMonad m => Ref SHA1 -> m (Maybe (Ref SHA1)) Source #

data SHA1 :: * #

SHA1 cryptographic hash algorithm

Instances

Data SHA1 

Methods

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 #

toConstr :: SHA1 -> Constr #

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 

Methods

showsPrec :: Int -> SHA1 -> ShowS #

show :: SHA1 -> String #

showList :: [SHA1] -> ShowS #

HashAlgorithm SHA1 
Resolvable (Ref SHA1) Source # 

Methods

resolve :: GitMonad m => Ref SHA1 -> m (Maybe (Ref SHA1)) Source #

type HashInternalContextSize SHA1 
type HashDigestSize SHA1 
type HashBlockSize SHA1 

class HashAlgorithm a where #

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.

Methods

hashDigestSize :: a -> Int #

Get the digest size of a hash algorithm

Instances

HashAlgorithm Blake2b_160 
HashAlgorithm Blake2b_224 
HashAlgorithm Blake2b_256 
HashAlgorithm Blake2b_384 
HashAlgorithm Blake2b_512 
HashAlgorithm Blake2bp_512 
HashAlgorithm Blake2s_160 
HashAlgorithm Blake2s_224 
HashAlgorithm Blake2s_256 
HashAlgorithm Blake2sp_224 
HashAlgorithm Blake2sp_256 
HashAlgorithm Keccak_224 
HashAlgorithm Keccak_256 
HashAlgorithm Keccak_384 
HashAlgorithm Keccak_512 
HashAlgorithm MD2 
HashAlgorithm MD4 
HashAlgorithm MD5 
HashAlgorithm RIPEMD160 
HashAlgorithm SHA1 
HashAlgorithm SHA224 
HashAlgorithm SHA256 
HashAlgorithm SHA3_224 
HashAlgorithm SHA3_256 
HashAlgorithm SHA3_384 
HashAlgorithm SHA3_512 
HashAlgorithm SHA384 
HashAlgorithm SHA512 
HashAlgorithm SHA512t_224 
HashAlgorithm SHA512t_256 
HashAlgorithm Skein256_224 
HashAlgorithm Skein256_256 
HashAlgorithm Skein512_224 
HashAlgorithm Skein512_256 
HashAlgorithm Skein512_384 
HashAlgorithm Skein512_512 
HashAlgorithm Tiger 
HashAlgorithm Whirlpool 
(IsDivisibleBy8 bitlen, KnownNat bitlen, IsAtLeast bitlen 8, IsAtMost bitlen 256) => HashAlgorithm (Blake2s bitlen) 

Associated Types

type HashBlockSize (Blake2s bitlen) :: Nat #

type HashDigestSize (Blake2s bitlen) :: Nat #

type HashInternalContextSize (Blake2s bitlen) :: Nat #

Methods

hashBlockSize :: Blake2s bitlen -> Int #

hashDigestSize :: Blake2s bitlen -> Int #

hashInternalContextSize :: Blake2s bitlen -> Int #

hashInternalInit :: Ptr (Context (Blake2s bitlen)) -> IO () #

hashInternalUpdate :: Ptr (Context (Blake2s bitlen)) -> Ptr Word8 -> Word32 -> IO () #

hashInternalFinalize :: Ptr (Context (Blake2s bitlen)) -> Ptr (Digest (Blake2s bitlen)) -> IO () #

(IsDivisibleBy8 bitlen, KnownNat bitlen, IsAtLeast bitlen 8, IsAtMost bitlen 512) => HashAlgorithm (Blake2b bitlen) 

Associated Types

type HashBlockSize (Blake2b bitlen) :: Nat #

type HashDigestSize (Blake2b bitlen) :: Nat #

type HashInternalContextSize (Blake2b bitlen) :: Nat #

Methods

hashBlockSize :: Blake2b bitlen -> Int #

hashDigestSize :: Blake2b bitlen -> Int #

hashInternalContextSize :: Blake2b bitlen -> Int #

hashInternalInit :: Ptr (Context (Blake2b bitlen)) -> IO () #

hashInternalUpdate :: Ptr (Context (Blake2b bitlen)) -> Ptr Word8 -> Word32 -> IO () #

hashInternalFinalize :: Ptr (Context (Blake2b bitlen)) -> Ptr (Digest (Blake2b bitlen)) -> IO () #

(IsDivisibleBy8 bitlen, KnownNat bitlen, IsAtLeast bitlen 8, IsAtMost bitlen 256) => HashAlgorithm (Blake2sp bitlen) 

Associated Types

type HashBlockSize (Blake2sp bitlen) :: Nat #

type HashDigestSize (Blake2sp bitlen) :: Nat #

type HashInternalContextSize (Blake2sp bitlen) :: Nat #

Methods

hashBlockSize :: Blake2sp bitlen -> Int #

hashDigestSize :: Blake2sp bitlen -> Int #

hashInternalContextSize :: Blake2sp bitlen -> Int #

hashInternalInit :: Ptr (Context (Blake2sp bitlen)) -> IO () #

hashInternalUpdate :: Ptr (Context (Blake2sp bitlen)) -> Ptr Word8 -> Word32 -> IO () #

hashInternalFinalize :: Ptr (Context (Blake2sp bitlen)) -> Ptr (Digest (Blake2sp bitlen)) -> IO () #

(IsDivisibleBy8 bitlen, KnownNat bitlen, IsAtLeast bitlen 8, IsAtMost bitlen 512) => HashAlgorithm (Blake2bp bitlen) 

Associated Types

type HashBlockSize (Blake2bp bitlen) :: Nat #

type HashDigestSize (Blake2bp bitlen) :: Nat #

type HashInternalContextSize (Blake2bp bitlen) :: Nat #

Methods

hashBlockSize :: Blake2bp bitlen -> Int #

hashDigestSize :: Blake2bp bitlen -> Int #

hashInternalContextSize :: Blake2bp bitlen -> Int #

hashInternalInit :: Ptr (Context (Blake2bp bitlen)) -> IO () #

hashInternalUpdate :: Ptr (Context (Blake2bp bitlen)) -> Ptr Word8 -> Word32 -> IO () #

hashInternalFinalize :: Ptr (Context (Blake2bp bitlen)) -> Ptr (Digest (Blake2bp bitlen)) -> IO () #

(IsDivisibleBy8 bitlen, KnownNat bitlen) => HashAlgorithm (SHAKE128 bitlen) 

Associated Types

type HashBlockSize (SHAKE128 bitlen) :: Nat #

type HashDigestSize (SHAKE128 bitlen) :: Nat #

type HashInternalContextSize (SHAKE128 bitlen) :: Nat #

Methods

hashBlockSize :: SHAKE128 bitlen -> Int #

hashDigestSize :: SHAKE128 bitlen -> Int #

hashInternalContextSize :: SHAKE128 bitlen -> Int #

hashInternalInit :: Ptr (Context (SHAKE128 bitlen)) -> IO () #

hashInternalUpdate :: Ptr (Context (SHAKE128 bitlen)) -> Ptr Word8 -> Word32 -> IO () #

hashInternalFinalize :: Ptr (Context (SHAKE128 bitlen)) -> Ptr (Digest (SHAKE128 bitlen)) -> IO () #

(IsDivisibleBy8 bitlen, KnownNat bitlen) => HashAlgorithm (SHAKE256 bitlen) 

Associated Types

type HashBlockSize (SHAKE256 bitlen) :: Nat #

type HashDigestSize (SHAKE256 bitlen) :: Nat #

type HashInternalContextSize (SHAKE256 bitlen) :: Nat #

Methods

hashBlockSize :: SHAKE256 bitlen -> Int #

hashDigestSize :: SHAKE256 bitlen -> Int #

hashInternalContextSize :: SHAKE256 bitlen -> Int #

hashInternalInit :: Ptr (Context (SHAKE256 bitlen)) -> IO () #

hashInternalUpdate :: Ptr (Context (SHAKE256 bitlen)) -> Ptr Word8 -> Word32 -> IO () #

hashInternalFinalize :: Ptr (Context (SHAKE256 bitlen)) -> Ptr (Digest (SHAKE256 bitlen)) -> IO () #

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.

Constructors

RefInvalid ByteString 

Instances

Eq RefInvalid Source # 
Data RefInvalid Source # 

Methods

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 # 
Exception RefInvalid Source # 

data RefNotFound hash Source #

Reference wasn't found

Constructors

RefNotFound (Ref hash) 

convert from bytestring and string

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

refPrefix :: Ref hash -> Int Source #

returns the prefix (leading byte) of this reference

cmpPrefix :: String -> Ref hash -> Ordering Source #

compare prefix

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 #