git-0.2.1: Git operations in haskell

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

Data.Git.Types

Contents

Description

 

Synopsis

Type of types

data ObjectType Source #

type of a git object.

Instances

Enum ObjectType Source #

the enum instance is useful when marshalling to pack file.

Eq ObjectType Source # 
Data ObjectType Source # 

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 # 

Main git types

data Tree hash Source #

Represent a root tree with zero to many tree entries.

Constructors

Tree 

Fields

Instances

Objectable Tree Source # 

Methods

getType :: Tree hash -> ObjectType Source #

getRaw :: Tree hash -> ByteString Source #

isDelta :: Tree hash -> Bool Source #

toObject :: Tree hash -> Object hash Source #

Eq (Tree hash) Source # 

Methods

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

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

Show (Tree hash) Source # 

Methods

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

show :: Tree hash -> String #

showList :: [Tree hash] -> ShowS #

Monoid (Tree hash) Source # 

Methods

mempty :: Tree hash #

mappend :: Tree hash -> Tree hash -> Tree hash #

mconcat :: [Tree hash] -> Tree hash #

data Commit hash Source #

Represent a commit object.

Instances

Objectable Commit Source # 
Eq (Commit hash) Source # 

Methods

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

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

Show (Commit hash) Source # 

Methods

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

show :: Commit hash -> String #

showList :: [Commit hash] -> ShowS #

data Blob hash Source #

Represent a binary blob.

Constructors

Blob 

Instances

Objectable Blob Source # 

Methods

getType :: Blob hash -> ObjectType Source #

getRaw :: Blob hash -> ByteString Source #

isDelta :: Blob hash -> Bool Source #

toObject :: Blob hash -> Object hash Source #

Eq (Blob hash) Source # 

Methods

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

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

Show (Blob hash) Source # 

Methods

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

show :: Blob hash -> String #

showList :: [Blob hash] -> ShowS #

data Tag hash Source #

Represent a signed tag.

Constructors

Tag 

Instances

Objectable Tag Source # 

Methods

getType :: Tag hash -> ObjectType Source #

getRaw :: Tag hash -> ByteString Source #

isDelta :: Tag hash -> Bool Source #

toObject :: Tag hash -> Object hash Source #

Eq (Tag hash) Source # 

Methods

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

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

Show (Tag hash) Source # 

Methods

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

show :: Tag hash -> String #

showList :: [Tag hash] -> ShowS #

data Person Source #

an author or committer line has the format: name email time timezone FIXME: should be a string, but I don't know if the data is stored consistantly in one encoding (UTF8)

Instances

modeperm type

data FilePermissions Source #

traditional unix permission for owner, group and permissions

Constructors

FilePermissions 

Fields

time type

data GitTime Source #

Git time is number of seconds since unix epoch in the UTC zone with the current timezone associated

Pack delta types

data DeltaOfs hash Source #

Delta pointing to an offset.

Constructors

DeltaOfs Word64 Delta 

Instances

Objectable DeltaOfs Source # 
Eq (DeltaOfs hash) Source # 

Methods

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

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

Show (DeltaOfs hash) Source # 

Methods

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

show :: DeltaOfs hash -> String #

showList :: [DeltaOfs hash] -> ShowS #

data DeltaRef hash Source #

Delta pointing to a ref.

Constructors

DeltaRef (Ref hash) Delta 

Instances

Objectable DeltaRef Source # 
Eq (DeltaRef hash) Source # 

Methods

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

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

Show (DeltaRef hash) Source # 

Methods

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

show :: DeltaRef hash -> String #

showList :: [DeltaRef hash] -> ShowS #

Basic types part of other bigger types

type TreeEnt hash = (ModePerm, EntName, Ref hash) Source #

represent one entry in the tree (permission,file or directory name,blob or tree ref) name should maybe a filepath, but not sure about the encoding.