License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | unix |
Safe Haskell | None |
Language | Haskell98 |
Data.Git.Storage.Object
Contents
Description
Synopsis
- data ObjectLocation hash
- data ObjectType
- type ObjectHeader hash = (ObjectType, Word64, Maybe (ObjectPtr hash))
- type ObjectData = ByteString
- data ObjectPtr hash
- data Object hash
- data ObjectInfo hash = ObjectInfo {
- oiHeader :: ObjectHeader hash
- oiData :: ObjectData
- oiChains :: [ObjectPtr hash]
- class Objectable a where
- getType :: a hash -> ObjectType
- getRaw :: a hash -> ByteString
- isDelta :: a hash -> Bool
- toObject :: a hash -> Object hash
- objectToType :: Object hash -> ObjectType
- objectTypeMarshall :: ObjectType -> String
- objectTypeUnmarshall :: ByteString -> ObjectType
- objectTypeIsDelta :: ObjectType -> Bool
- objectIsDelta :: Object hash -> Bool
- objectToTree :: Object hash -> Maybe (Tree hash)
- objectToCommit :: Object hash -> Maybe (Commit hash)
- objectToTag :: Object hash -> Maybe (Tag hash)
- objectToBlob :: Object hash -> Maybe (Blob hash)
- treeParse :: HashAlgorithm hash => Parser (Tree hash)
- commitParse :: HashAlgorithm hash => Parser (Commit hash)
- tagParse :: HashAlgorithm hash => Parser (Tag hash)
- blobParse :: Parser (Blob hash)
- objectParseTree :: HashAlgorithm hash => Parser (Object hash)
- objectParseCommit :: HashAlgorithm hash => Parser (Object hash)
- objectParseTag :: HashAlgorithm hash => Parser (Object hash)
- objectParseBlob :: HashAlgorithm hash => Parser (Object hash)
- objectWriteHeader :: ObjectType -> Word64 -> ByteString
- objectWrite :: Object hash -> ByteString
- objectHash :: HashAlgorithm hash => ObjectType -> Word64 -> ByteString -> Ref hash
Documentation
data ObjectLocation hash Source #
location of an object in the database
Instances
Eq (ObjectLocation hash) Source # | |
Defined in Data.Git.Storage.Object Methods (==) :: ObjectLocation hash -> ObjectLocation hash -> Bool # (/=) :: ObjectLocation hash -> ObjectLocation hash -> Bool # | |
Show (ObjectLocation hash) Source # | |
Defined in Data.Git.Storage.Object Methods showsPrec :: Int -> ObjectLocation hash -> ShowS # show :: ObjectLocation hash -> String # showList :: [ObjectLocation hash] -> ShowS # |
data ObjectType Source #
type of a git object.
Constructors
TypeTree | |
TypeBlob | |
TypeCommit | |
TypeTag | |
TypeDeltaOff | |
TypeDeltaRef |
Instances
Enum ObjectType Source # | the enum instance is useful when marshalling to pack file. |
Defined in Data.Git.Types Methods succ :: ObjectType -> ObjectType # pred :: ObjectType -> ObjectType # toEnum :: Int -> ObjectType # fromEnum :: ObjectType -> Int # enumFrom :: ObjectType -> [ObjectType] # enumFromThen :: ObjectType -> ObjectType -> [ObjectType] # enumFromTo :: ObjectType -> ObjectType -> [ObjectType] # enumFromThenTo :: ObjectType -> ObjectType -> ObjectType -> [ObjectType] # | |
Eq ObjectType Source # | |
Defined in Data.Git.Types | |
Data ObjectType Source # | |
Defined in Data.Git.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjectType -> c ObjectType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjectType # toConstr :: ObjectType -> Constr # dataTypeOf :: ObjectType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjectType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjectType) # gmapT :: (forall b. Data b => b -> b) -> ObjectType -> ObjectType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjectType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjectType -> r # gmapQ :: (forall d. Data d => d -> u) -> ObjectType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjectType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjectType -> m ObjectType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectType -> m ObjectType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectType -> m ObjectType # | |
Show ObjectType Source # | |
Defined in Data.Git.Types Methods showsPrec :: Int -> ObjectType -> ShowS # show :: ObjectType -> String # showList :: [ObjectType] -> ShowS # |
type ObjectHeader hash = (ObjectType, Word64, Maybe (ObjectPtr hash)) Source #
type ObjectData = ByteString Source #
Delta objects points to some others objects in the database either as offset in the pack or as a direct reference.
describe a git object, that could of 6 differents types: tree, blob, commit, tag and deltas (offset or ref). the deltas one are only available in packs.
Constructors
ObjCommit (Commit hash) | |
ObjTag (Tag hash) | |
ObjBlob (Blob hash) | |
ObjTree (Tree hash) | |
ObjDeltaOfs (DeltaOfs hash) | |
ObjDeltaRef (DeltaRef hash) |
data ObjectInfo hash Source #
Raw objects infos have an header (type, size, ptr), the data and a pointers chains to parents for resolved objects.
Constructors
ObjectInfo | |
Fields
|
Instances
Eq (ObjectInfo hash) Source # | |
Defined in Data.Git.Storage.Object Methods (==) :: ObjectInfo hash -> ObjectInfo hash -> Bool # (/=) :: ObjectInfo hash -> ObjectInfo hash -> Bool # | |
Show (ObjectInfo hash) Source # | |
Defined in Data.Git.Storage.Object Methods showsPrec :: Int -> ObjectInfo hash -> ShowS # show :: ObjectInfo hash -> String # showList :: [ObjectInfo hash] -> ShowS # |
class Objectable a where Source #
Methods
getType :: a hash -> ObjectType Source #
getRaw :: a hash -> ByteString Source #
objectToType :: Object hash -> ObjectType Source #
objectTypeIsDelta :: ObjectType -> Bool Source #
objectIsDelta :: Object hash -> Bool Source #
parsing function
treeParse :: HashAlgorithm hash => Parser (Tree hash) Source #
parse a tree content
commitParse :: HashAlgorithm hash => Parser (Commit hash) Source #
parse a commit content
tagParse :: HashAlgorithm hash => Parser (Tag hash) Source #
parse a tag content
objectParseTree :: HashAlgorithm hash => Parser (Object hash) Source #
objectParseCommit :: HashAlgorithm hash => Parser (Object hash) Source #
objectParseTag :: HashAlgorithm hash => Parser (Object hash) Source #
objectParseBlob :: HashAlgorithm hash => Parser (Object hash) Source #
writing function
objectWriteHeader :: ObjectType -> Word64 -> ByteString Source #
objectWrite :: Object hash -> ByteString Source #
objectHash :: HashAlgorithm hash => ObjectType -> Word64 -> ByteString -> Ref hash Source #