gitlib-2.0.0.0: API library for working with Git repositories

Safe HaskellNone

Git.Types

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

data Tree m :: *Source

data Options m :: *Source

Methods

facts :: m RepositoryFactsSource

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

deleteRepository :: m ()Source

createReference :: Text -> RefTarget m -> m ()Source

lookupReference :: Text -> m (Maybe (RefTarget m))Source

updateReference :: Text -> RefTarget m -> m ()Source

deleteReference :: Text -> m ()Source

listReferences :: m [Text]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 :: Oid m -> m (Object m)Source

existsObject :: Oid m -> m BoolSource

listObjectsSource

Arguments

:: Maybe (CommitOid m)

A commit we may already have

-> CommitOid m

The commit we need

-> Bool

Include commit trees also?

-> m [ObjectOid m]

All the objects in between

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

treeOid :: Tree m -> TreeOid mSource

treeEntry :: Tree m -> Text -> m (Maybe (TreeEntry m))Source

listTreeEntries :: Tree m -> m [(Text, TreeEntry m)]Source

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

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

createCommit :: [CommitOid m] -> TreeOid m -> Signature -> Signature -> Text -> Maybe Text -> m (Commit m)Source

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

pushCommit :: (MonadTrans t, MonadGit m, MonadGit (t m), Repository m, Repository (t m)) => CommitOid m -> Maybe Text -> Text -> t m (CommitOid (t 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

Instances

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

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

copyOid :: (Repository m, Repository n) => Oid m -> n (Oid n)Source

newtype SHA Source

Constructors

SHA ByteString 
 

data Blob m Source

Constructors

Blob 

Fields

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

data TreeEntry m Source

Constructors

BlobEntry 
TreeEntry 

Fields

treeEntryOid :: !(TreeOid m)
 
CommitEntry 

Fields

commitEntryOid :: !(CommitOid m)
 

Instances

 
 

data Tag m Source

Constructors

Tag 

Fields

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

data Object m Source

Constructors

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

data RefTarget m Source

Constructors

RefObj !(CommitOid m) 
RefSymbolic !Text