git-0.3.0: Git operations in haskell

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

Data.Git.Storage.Object

Contents

Description

 
Synopsis

Documentation

data ObjectLocation hash Source #

location of an object in the database

Constructors

NotFound 
Loose (Ref hash) 
Packed (Ref hash) Word64 
Instances
Eq (ObjectLocation hash) Source # 
Instance details

Defined in Data.Git.Storage.Object

Methods

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

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

Show (ObjectLocation hash) Source # 
Instance details

Defined in Data.Git.Storage.Object

data ObjectType Source #

type of a git object.

Instances
Enum ObjectType Source #

the enum instance is useful when marshalling to pack file.

Instance details

Defined in Data.Git.Types

Eq ObjectType Source # 
Instance details

Defined in Data.Git.Types

Data ObjectType Source # 
Instance details

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 # 
Instance details

Defined in Data.Git.Types

data ObjectPtr hash Source #

Delta objects points to some others objects in the database either as offset in the pack or as a direct reference.

Constructors

PtrRef (Ref hash) 
PtrOfs Word64 
Instances
Eq (ObjectPtr hash) Source # 
Instance details

Defined in Data.Git.Storage.Object

Methods

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

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

Show (ObjectPtr hash) Source # 
Instance details

Defined in Data.Git.Storage.Object

Methods

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

show :: ObjectPtr hash -> String #

showList :: [ObjectPtr hash] -> ShowS #

data Object hash Source #

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) 
Instances
Eq (Object hash) Source # 
Instance details

Defined in Data.Git.Storage.Object

Methods

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

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

Show (Object hash) Source # 
Instance details

Defined in Data.Git.Storage.Object

Methods

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

show :: Object hash -> String #

showList :: [Object hash] -> ShowS #

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 # 
Instance details

Defined in Data.Git.Storage.Object

Methods

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

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

Show (ObjectInfo hash) Source # 
Instance details

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 #

isDelta :: a hash -> Bool Source #

toObject :: a hash -> Object hash Source #

Instances
Objectable DeltaRef Source # 
Instance details

Defined in Data.Git.Storage.Object

Objectable DeltaOfs Source # 
Instance details

Defined in Data.Git.Storage.Object

Objectable Tag Source # 
Instance details

Defined in Data.Git.Storage.Object

Methods

getType :: Tag hash -> ObjectType Source #

getRaw :: Tag hash -> ByteString Source #

isDelta :: Tag hash -> Bool Source #

toObject :: Tag hash -> Object hash Source #

Objectable Commit Source # 
Instance details

Defined in Data.Git.Storage.Object

Objectable Blob Source # 
Instance details

Defined in Data.Git.Storage.Object

Methods

getType :: Blob hash -> ObjectType Source #

getRaw :: Blob hash -> ByteString Source #

isDelta :: Blob hash -> Bool Source #

toObject :: Blob hash -> Object hash Source #

Objectable Tree Source # 
Instance details

Defined in Data.Git.Storage.Object

Methods

getType :: Tree hash -> ObjectType Source #

getRaw :: Tree hash -> ByteString Source #

isDelta :: Tree hash -> Bool Source #

toObject :: Tree hash -> Object hash Source #

objectToTree :: Object hash -> Maybe (Tree hash) Source #

objectToTag :: Object hash -> Maybe (Tag hash) Source #

objectToBlob :: Object hash -> Maybe (Blob hash) 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

blobParse :: Parser (Blob hash) Source #

parse a blob 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