gitlib-1.2.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, IsOid (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

type Oid m :: *Source

type TreeKind m :: *Source

type Tree m :: * -> *Source

data Options m Source

Methods

facts :: m RepositoryFactsSource

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

parseObjOid :: forall o. Text -> m (Tagged o (Oid m))Source

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 (RepositoryTree 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 (RepositoryTree m)Source

cloneTree :: RepositoryTree m -> m (RepositoryTree m)Source

traverseEntries :: (FilePath -> TreeEntry m -> m a) -> RepositoryTree m -> m [a]Source

traverseEntries_ :: (FilePath -> TreeEntry m -> m a) -> RepositoryTree m -> m ()Source

writeTree :: RepositoryTree m -> m (TreeOid m)Source

unsafeUpdateTree :: RepositoryTree m -> FilePath -> Bool -> (Maybe (TreeEntry m) -> ModifyTreeResult m) -> m (RepositoryTree m, Maybe (TreeEntry 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

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 ()
 

class (Eq o, Ord o, Show o) => IsOid o whereSource

data Object m Source

Constructors

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

data ObjRef m a Source

Constructors

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

data Blob m Source

Constructors

Blob 

Fields

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

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

type BlobRef m = ObjRef m (Blob m)Source

data TreeT t m a Source

Instances

MonadTrans (TreeT t) 
Monad m => Monad (TreeT t m) 
Functor m => Functor (TreeT t m) 
MonadFix m => MonadFix (TreeT t m) 
MonadPlus m => MonadPlus (TreeT t m) 
(Functor m, Monad m) => Applicative (TreeT t m) 
(Functor m, MonadPlus m) => Alternative (TreeT t m) 
MonadIO m => MonadIO (TreeT t m) 

data TreeEntry m Source

Constructors

BlobEntry 
TreeEntry 

Fields

treeEntryRef :: !(TreeRef m)
 
CommitEntry 

Fields

commitEntryRef :: !(CommitOid m)
 

treeRef :: RepositoryTree m -> TreeRef mSource

A Tree is anything that is treeish.

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

data Tag m Source

Constructors

Tag 

Fields

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

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

type TagRef m = ObjRef m (Tag 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)