gitlib-1.0.1: API library for working with Git repositories

Safe HaskellNone

Git

Description

Interface for working with Git repositories.

Synopsis

Documentation

 

class (Applicative m, Monad m, Failure GitException m, Eq (Oid m), Ord (Oid m), Show (Oid m)) => Repository m whereSource

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

Associated Types

data Oid m Source

data TreeData m Source

data Options m Source

Methods

facts :: m RepositoryFactsSource

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

renderOid :: Oid m -> TextSource

renderObjOid :: Tagged a (Oid m) -> TextSource

createRef :: Text -> RefTarget m (Commit m) -> m (Reference m (Commit m))Source

createRef_ :: Text -> RefTarget m (Commit m) -> m ()Source

lookupRef :: Text -> m (Maybe (Reference m (Commit m)))Source

updateRef :: Text -> RefTarget m (Commit m) -> m (Reference m (Commit m))Source

updateRef_ :: Text -> RefTarget m (Commit m) -> m ()Source

deleteRef :: Text -> m ()Source

allRefs :: m [Reference m (Commit m)]Source

allRefNames :: m [Text]Source

resolveRef :: Text -> m (Maybe (CommitRef m))Source

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

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

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

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

lookupObject :: Text -> m (Object m)Source

existsObject :: Oid m -> m BoolSource

traverseObjects :: forall a. (Object m -> m a) -> Maybe (CommitName m) -> m [a]Source

traverseObjects_ :: (Object m -> m ()) -> Maybe (CommitName m) -> m ()Source

pushCommit :: (MonadTrans t, MonadGit m, MonadGit (t m), Repository m, Repository (t m)) => CommitName m -> Maybe Text -> Text -> t m (CommitRef (t m))Source

traverseCommits :: forall a. (CommitRef m -> m a) -> CommitName m -> m [a]Source

traverseCommits_ :: (CommitRef m -> m ()) -> CommitName m -> m ()Source

missingObjectsSource

Arguments

:: Maybe (CommitName m)

A commit we may already have

-> CommitName m

The commit we need

-> m [Object m]

All the objects in between

newTree :: m (Tree m)Source

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

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

createCommit :: [CommitRef m] -> TreeRef m -> Signature -> Signature -> Text -> Maybe Text -> m (Commit m)Source

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

deleteRepository :: m ()Source

buildPackFile :: FilePath -> [Either (CommitOid m) (TreeOid m)] -> m FilePathSource

buildPackIndex :: FilePath -> ByteString -> m (Text, FilePath, FilePath)Source

writePackFile :: FilePath -> m ()Source

remoteFetch :: Text -> Text -> m ()Source

 
 

type BlobOid m = Tagged (Blob m) (Oid m)Source

type TreeOid m = Tagged (Tree m) (Oid m)Source

type CommitOid m = Tagged (Commit m) (Oid m)Source

type TagOid m = Tagged (Tag m) (Oid m)Source

 

data RefTarget m a Source

Constructors

RefObj !(ObjRef m a) 
RefSymbolic !Text 

data Reference m a Source

Constructors

Reference 

Fields

refName :: !Text
 
refTarget :: !(RefTarget m a)
 
 

data ObjRef m a Source

Constructors

ByOid !(Tagged a (Oid m)) 
Known !a 

type BlobRef m = ObjRef m (Blob m)Source

type TreeRef m = ObjRef m (Tree m)Source

type TagRef m = ObjRef m (Tag m)Source

data Object m Source

Constructors

BlobObj !(BlobRef m) 
TreeObj !(TreeRef m) 
CommitObj !(CommitRef m) 
TagObj !(TagRef m) 
 

data Blob m Source

Constructors

Blob 

Fields

blobOid :: !(BlobOid m)
 
blobContents :: !(BlobContents m)
 
 

data TreeEntry m Source

Constructors

BlobEntry 
TreeEntry 

Fields

treeEntryRef :: !(TreeRef m)
 
CommitEntry 

Fields

commitEntryRef :: !(CommitOid m)
 

data Tree m Source

A Tree is anything that is treeish.

Minimal complete definition: modifyTree. Note that for some treeish things, like Tags, it should always be an error to attempt to modify the tree in any way.

Constructors

Tree 

Fields

modifyTree :: FilePath -> Bool -> (Maybe (TreeEntry m) -> m (ModifyTreeResult m)) -> m (Maybe (TreeEntry m))
 
lookupEntry :: FilePath -> m (Maybe (TreeEntry m))
 
putTreeEntry :: FilePath -> TreeEntry m -> m ()
 
putBlob' :: FilePath -> BlobOid m -> BlobKind -> m ()
 
putBlob :: FilePath -> BlobOid m -> m ()
 
putTree :: FilePath -> TreeRef m -> m ()
 
putCommit :: FilePath -> CommitOid m -> m ()
 
dropFromTree :: FilePath -> m ()
 
writeTree :: m (TreeOid m)
 
traverseEntries :: forall a. (FilePath -> TreeEntry m -> m a) -> m [a]
 
traverseEntries_ :: (FilePath -> TreeEntry m -> m ()) -> m ()
 
getTreeData :: !(TreeData m)
 

mkTree :: Repository m => (Tree m -> FilePath -> Bool -> (Maybe (TreeEntry m) -> m (ModifyTreeResult m)) -> m (Maybe (TreeEntry m))) -> (Tree m -> m (TreeOid m)) -> (forall a. Tree m -> (FilePath -> TreeEntry m -> m a) -> m [a]) -> TreeData m -> Tree mSource

 
 

data Tag m Source

Constructors

Tag 

Fields

tagOid :: !(TagOid m)
 
tagCommit :: !(CommitRef m)
 
 
 

data RepositoryFactory t m c Source

Constructors

RepositoryFactory 

Fields

openRepository :: RepositoryOptions -> m c
 
runRepository :: forall a. c -> t m a -> m a
 
closeRepository :: c -> m ()
 
getRepository :: t m c
 
defaultOptions :: !RepositoryOptions
 
startupBackend :: m ()
 
shutdownBackend :: m ()