gitlib-2.1.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

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 !RefName 

Instances