git-0.2.2: Git operations in haskell

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

Data.Git

Contents

Description

 
Synopsis

Basic types

data Ref hash Source #

represent a git reference (SHA1)

Instances
Eq (Ref hash) Source # 
Instance details

Defined in Data.Git.Ref

Methods

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

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

Ord (Ref hash) Source # 
Instance details

Defined in Data.Git.Ref

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

Defined in Data.Git.Ref

Methods

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

show :: Ref hash -> String #

showList :: [Ref hash] -> ShowS #

Resolvable (Ref SHA1) Source # 
Instance details

Defined in Data.Git.Monad

Methods

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

newtype RefName Source #

Constructors

RefName 

Fields

Instances
Eq RefName Source # 
Instance details

Defined in Data.Git.Named

Methods

(==) :: RefName -> RefName -> Bool #

(/=) :: RefName -> RefName -> Bool #

Ord RefName Source # 
Instance details

Defined in Data.Git.Named

Show RefName Source # 
Instance details

Defined in Data.Git.Named

IsString RefName Source # 
Instance details

Defined in Data.Git.Named

Methods

fromString :: String -> RefName #

Resolvable RefName Source # 
Instance details

Defined in Data.Git.Monad

Methods

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

data Commit hash Source #

Represent a commit object.

Instances
Objectable Commit Source # 
Instance details

Defined in Data.Git.Storage.Object

Eq (Commit hash) Source # 
Instance details

Defined in Data.Git.Types

Methods

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

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

Show (Commit hash) Source # 
Instance details

Defined in Data.Git.Types

Methods

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

show :: Commit hash -> String #

showList :: [Commit 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
Eq Person Source # 
Instance details

Defined in Data.Git.Types

Methods

(==) :: Person -> Person -> Bool #

(/=) :: Person -> Person -> Bool #

Show Person Source # 
Instance details

Defined in Data.Git.Types

newtype Tree hash Source #

Represent a root tree with zero to many tree entries.

Constructors

Tree 

Fields

Instances
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 #

Eq (Tree hash) Source # 
Instance details

Defined in Data.Git.Types

Methods

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

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

Show (Tree hash) Source # 
Instance details

Defined in Data.Git.Types

Methods

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

show :: Tree hash -> String #

showList :: [Tree hash] -> ShowS #

newtype Blob hash Source #

Represent a binary blob.

Constructors

Blob 
Instances
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 #

Eq (Blob hash) Source # 
Instance details

Defined in Data.Git.Types

Methods

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

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

Show (Blob hash) Source # 
Instance details

Defined in Data.Git.Types

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

Eq (Tag hash) Source # 
Instance details

Defined in Data.Git.Types

Methods

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

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

Show (Tag hash) Source # 
Instance details

Defined in Data.Git.Types

Methods

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

show :: Tag hash -> String #

showList :: [Tag hash] -> ShowS #

data GitTime Source #

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

Instances
Eq GitTime Source # 
Instance details

Defined in Data.Git.Types

Methods

(==) :: GitTime -> GitTime -> Bool #

(/=) :: GitTime -> GitTime -> Bool #

Show GitTime Source # 
Instance details

Defined in Data.Git.Types

Timeable GitTime Source # 
Instance details

Defined in Data.Git.Types

Time GitTime Source # 
Instance details

Defined in Data.Git.Types

newtype ModePerm Source #

Constructors

ModePerm Word32 
Instances
Eq ModePerm Source # 
Instance details

Defined in Data.Git.Types

Show ModePerm Source # 
Instance details

Defined in Data.Git.Types

data EntName Source #

Entity name

Instances
Eq EntName Source # 
Instance details

Defined in Data.Git.Types

Methods

(==) :: EntName -> EntName -> Bool #

(/=) :: EntName -> EntName -> Bool #

Ord EntName Source # 
Instance details

Defined in Data.Git.Types

Show EntName Source # 
Instance details

Defined in Data.Git.Types

IsString EntName Source # 
Instance details

Defined in Data.Git.Types

Methods

fromString :: String -> EntName #

Byteable EntName Source # 
Instance details

Defined in Data.Git.Types

Helper & type related to ModePerm

data FilePermissions Source #

traditional unix permission for owner, group and permissions

Constructors

FilePermissions 

Fields

Revision

data Revision Source #

A git revision. this can be many things: * a shorten ref * a ref * a named branch or tag followed by optional modifiers RevModifier that can represent: * parenting * type * date

Instances
Eq Revision Source # 
Instance details

Defined in Data.Git.Revision

Data Revision Source # 
Instance details

Defined in Data.Git.Revision

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Revision -> c Revision #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Revision #

toConstr :: Revision -> Constr #

dataTypeOf :: Revision -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Revision) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Revision) #

gmapT :: (forall b. Data b => b -> b) -> Revision -> Revision #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Revision -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Revision -> r #

gmapQ :: (forall d. Data d => d -> u) -> Revision -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Revision -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Revision -> m Revision #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Revision -> m Revision #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Revision -> m Revision #

Show Revision Source # 
Instance details

Defined in Data.Git.Revision

IsString Revision Source # 
Instance details

Defined in Data.Git.Revision

Resolvable Revision Source # 
Instance details

Defined in Data.Git.Monad

Methods

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

resolveRevision :: (Typeable hash, HashAlgorithm hash) => Git hash -> Revision -> IO (Maybe (Ref hash)) Source #

try to resolve a string to a specific commit ref for example: HEAD, HEAD^, master~3, shortRef

Object resolution

resolveTreeish :: HashAlgorithm hash => Git hash -> Ref hash -> IO (Maybe (Tree hash)) Source #

returns a tree from a ref that might be either a commit, a tree or a tag.

resolvePath Source #

Arguments

:: (Typeable hash, HashAlgorithm hash) 
=> Git hash

repository

-> Ref hash

commit reference

-> EntPath

paths

-> IO (Maybe (Ref hash)) 

resolve the ref (tree or blob) related to a path at a specific commit ref

repo context

data Git hash Source #

represent a git repo, with possibly already opened filereaders for indexes and packs

withCurrentRepo :: (Git SHA1 -> IO a) -> IO a Source #

execute a function on the current repository.

check findRepo to see how the git repository is found.

withRepo :: LocalPath -> (Git SHA1 -> IO c) -> IO c Source #

execute a function f with a git context.

findRepo :: IO LocalPath Source #

Find the git repository from the current directory.

If the environment variable GIT_DIR is set then it's used, otherwise iterate from current directory, up to 128 parents for a .git directory

Repository queries and creation

initRepo :: LocalPath -> IO () Source #

initialize a new repository at a specific location.

isRepo :: LocalPath -> IO Bool Source #

basic checks to see if a specific path looks like a git repo.

Context operations

rewrite Source #

Arguments

:: (Typeable hash, HashAlgorithm hash) 
=> Git hash

Repository

-> (Commit hash -> IO (Commit hash))

Mapping function

-> Revision

revision to start from

-> Int

the number of parents to map

-> IO (Ref hash)

return the new head REF

Rewrite a set of commits from a revision and returns the new ref.

If during revision traversal (diving) there's a commit with zero or multiple parents then the traversal will stop regardless of the amount of parent requested.

calling "rewrite f 2 (revisionOf d)" on the following tree:

a <-- b <-- c <-- d

result in the following tree after mapping with f:

a <-- f(b) <-- f(c) <-- f(d)

Get objects

getObject Source #

Arguments

:: HashAlgorithm hash 
=> Git hash

repository

-> Ref hash

the object's reference to

-> Bool

whether to resolve deltas if found

-> IO (Maybe (Object hash))

returned object if found

get an object from repository using a ref.

getCommit :: (Typeable hash, HashAlgorithm hash) => Git hash -> Ref hash -> IO (Commit hash) Source #

get a specified commit but raises an exception if doesn't exists or type is not appropriate

getTree :: (Typeable hash, HashAlgorithm hash) => Git hash -> Ref hash -> IO (Tree hash) Source #

get a specified tree but raise

Set objects

setObject :: HashAlgorithm hash => Git hash -> Object hash -> IO (Ref hash) Source #

set an object in the store and returns the new ref this is always going to create a loose object.

toObject :: Objectable a => a hash -> Object hash Source #

Work trees

type WorkTree hash = MVar (TreeSt hash) Source #

data EntType Source #

Instances
Eq EntType Source # 
Instance details

Defined in Data.Git.WorkTree

Methods

(==) :: EntType -> EntType -> Bool #

(/=) :: EntType -> EntType -> Bool #

Show EntType Source # 
Instance details

Defined in Data.Git.WorkTree

workTreeNew :: IO (WorkTree hash) Source #

Create a new worktree

workTreeFrom :: Ref hash -> IO (WorkTree hash) Source #

Create a worktree from a tree reference.

workTreeDelete :: (Typeable hash, HashAlgorithm hash) => Git hash -> WorkTree hash -> EntPath -> IO () Source #

delete a path from a working tree

if the path doesn't exist, no error is raised

workTreeSet :: (Typeable hash, HashAlgorithm hash) => Git hash -> WorkTree hash -> EntPath -> (EntType, Ref hash) -> IO () Source #

Set a file in this working tree to a specific ref.

The ref should point to a valid blob or tree object, and it's safer to write the referenced tree or blob object first.

workTreeFlush :: HashAlgorithm hash => Git hash -> WorkTree hash -> IO (Ref hash) Source #

Flush the worktree by creating all the necessary trees in the git store and return the root ref of the work tree.

Named refs

branchWrite Source #

Arguments

:: Git hash

repository

-> RefName

the name of the branch to write

-> Ref hash

the reference to set

-> IO () 

Write a branch to point to a specific reference

branchList :: Git hash -> IO (Set RefName) Source #

Return the list of branches

tagWrite Source #

Arguments

:: Git hash

repository

-> RefName

the name of the tag to write

-> Ref hash

the reference to set

-> IO () 

Write a tag to point to a specific reference

tagList :: Git hash -> IO (Set RefName) Source #

Return the list of branches

headSet Source #

Arguments

:: Git hash

repository

-> Either (Ref hash) RefName

either a raw reference or a branch name

-> IO () 

Set head to point to either a reference or a branch name.

headGet :: HashAlgorithm hash => Git hash -> IO (Either (Ref hash) RefName) Source #

Get what the head is pointing to, or the reference otherwise