gitlib-3.1.2: API library for working with Git repositories

Safe HaskellNone
LanguageHaskell98

Git.Types

Synopsis

Documentation

class (Applicative m, Monad m, MonadThrow m, IsOid (Oid r), Show (Oid r), Eq (Oid r), Ord (Oid r)) => MonadGit r m | m -> r where Source #

Repository is the central point of contact between user code and Git data objects. Every object must belong to some repository.

Associated Types

type Oid r :: * Source #

data Tree r :: * Source #

data Options r :: * Source #

Methods

facts :: m RepositoryFacts Source #

parseOid :: Text -> m (Oid r) Source #

getRepository :: m r Source #

closeRepository :: m () Source #

deleteRepository :: m () Source #

createReference :: RefName -> RefTarget r -> m () Source #

lookupReference :: RefName -> m (Maybe (RefTarget r)) Source #

updateReference :: RefName -> RefTarget r -> m () Source #

deleteReference :: RefName -> m () Source #

sourceReferences :: ConduitT i RefName m () Source #

lookupObject :: Oid r -> m (Object r m) Source #

existsObject :: Oid r -> m Bool Source #

sourceObjects Source #

Arguments

:: Maybe (CommitOid r)

A commit we may already have

-> CommitOid r

The commit we need

-> Bool

Include commit trees also?

-> ConduitT i (ObjectOid r) m ()

All the objects in between

lookupCommit :: CommitOid r -> m (Commit r) Source #

lookupTree :: TreeOid r -> m (Tree r) Source #

lookupBlob :: BlobOid r -> m (Blob r m) Source #

lookupTag :: TagOid r -> m (Tag r) Source #

readIndex :: TreeT r m () Source #

writeIndex :: TreeT r m () Source #

newTreeBuilder :: Maybe (Tree r) -> m (TreeBuilder r m) Source #

treeOid :: Tree r -> m (TreeOid r) Source #

treeEntry :: Tree r -> TreeFilePath -> m (Maybe (TreeEntry r)) Source #

sourceTreeEntries :: Tree r -> ConduitT i (TreeFilePath, TreeEntry r) m () Source #

diffContentsWithTree :: ConduitT () (Either TreeFilePath ByteString) m () -> Tree r -> ConduitT i ByteString m () Source #

hashContents :: BlobContents m -> m (BlobOid r) Source #

createBlob :: BlobContents m -> m (BlobOid r) Source #

createCommit :: [CommitOid r] -> TreeOid r -> Signature -> Signature -> CommitMessage -> Maybe RefName -> m (Commit r) Source #

createTag :: CommitOid r -> Signature -> CommitMessage -> Text -> m (Tag r) Source #

data RepositoryFactory n m r Source #

Constructors

RepositoryFactory 

Fields

 

class IsOid o where Source #

type BlobOid r = Tagged r (Oid r) Source #

type TreeOid r = Tagged (Tree r) (Oid r) Source #

type CommitOid r = Tagged (Commit r) (Oid r) Source #

type TagOid r = Tagged (Tag r) (Oid r) Source #

parseObjOid :: MonadGit r m => forall o. Text -> m (Tagged o (Oid r)) Source #

copyOid :: (MonadGit r m, MonadGit s n) => Oid r -> n (Oid s) Source #

newtype SHA Source #

Constructors

SHA 

Fields

Instances

Eq SHA Source # 

Methods

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

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

Ord SHA Source # 

Methods

compare :: SHA -> SHA -> Ordering #

(<) :: SHA -> SHA -> Bool #

(<=) :: SHA -> SHA -> Bool #

(>) :: SHA -> SHA -> Bool #

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

max :: SHA -> SHA -> SHA #

min :: SHA -> SHA -> SHA #

Read SHA Source # 
Show SHA Source # 

Methods

showsPrec :: Int -> SHA -> ShowS #

show :: SHA -> String #

showList :: [SHA] -> ShowS #

Hashable SHA Source # 

Methods

hashWithSalt :: Int -> SHA -> Int #

hash :: SHA -> Int #

IsOid SHA Source # 
 

data Blob r m Source #

Constructors

Blob 

Fields

 

newtype TreeT r m a Source #

Constructors

TreeT 

Fields

data TreeEntry r Source #

Constructors

BlobEntry 
TreeEntry 

Fields

CommitEntry 

Fields

 
 

data Tag r Source #

Constructors

Tag 

Fields

 

data Object r m Source #

Constructors

BlobObj !(Blob r m) 
TreeObj !(Tree r) 
CommitObj !(Commit r) 
TagObj !(Tag r) 

objectOid :: MonadGit r m => Object r m -> m (Oid r) Source #

loadObject :: MonadGit r m => ObjectOid r -> m (Object r m) Source #

 

data RefTarget (r :: *) Source #

Constructors

RefObj !(Oid r) 
RefSymbolic !RefName 
 

data ModificationKind Source #

 

data GitException Source #

There is a separate GitException for each possible failure when interacting with the Git repository.