Safe Haskell | None |
---|
Git.Libgit2
Description
Interface for opening and creating repositories. Repository objects are immutable, and serve only to refer to the given repository. Any data associated with the repository — such as the list of branches — is queried as needed.
Documentation
newtype LgRepository m a Source
Constructors
LgRepository | |
Fields
|
Instances
MonadTrans LgRepository | |
MonadTransControl LgRepository | |
(MonadIO m, MonadBaseControl IO m) => MonadBaseControl IO (LgRepository m) | |
(Monad m, MonadIO m, Applicative m) => MonadBase IO (LgRepository m) | |
Monad m => Monad (LgRepository m) | |
Functor m => Functor (LgRepository m) | |
Applicative m => Applicative (LgRepository m) | |
Monad m => MonadUnsafeIO (LgRepository m) | |
Monad m => MonadThrow (LgRepository m) | |
MonadGit m => Repository (LgRepository m) | |
MonadIO m => MonadIO (LgRepository m) |
type BlobOid m = BlobOid (LgRepository m)Source
type Commit m = Commit (LgRepository m)Source
type CommitOid m = CommitOid (LgRepository m)Source
type CommitRef m = CommitRef (LgRepository m)Source
type family Oid m1 :: *
Constructors
OidPtr | |
Fields
|
mkOid :: ForeignPtr C'git_oid -> OidPtrSource
type Reference m = Reference (LgRepository m) (Commit m)Source
data Repository Source
Constructors
Repository | |
Fields
|
Instances
type Tree m = Tree (LgRepository m)Source
type TreeOid m = TreeOid (LgRepository m)Source
type TreeRef m = TreeRef (LgRepository m)Source
addTracingBackend :: MonadGit m => LgRepository m ()Source
checkResult :: (Eq a, Num a, Failure GitException m) => a -> Text -> m ()Source
closeLgRepository :: MonadGit m => Repository -> m ()Source
lgBuildPackIndex :: FilePath -> ByteString -> IO (Text, FilePath, FilePath)Source
lgGet :: Monad m => LgRepository m RepositorySource
lgExcTrap :: Monad m => LgRepository m (IORef (Maybe GitException))Source
lgLoadPackFileInMemory :: FilePath -> Ptr (Ptr C'git_odb_backend) -> Ptr (Ptr C'git_odb) -> ResourceT IO (Ptr C'git_odb)Source
lgReadFromPack :: FilePath -> SHA -> Bool -> IO (Maybe (C'git_otype, CSize, ByteString))Source
shaToOid :: SHA -> IO (ForeignPtr C'git_oid)Source
openLgRepository :: MonadGit m => RepositoryOptions -> m RepositorySource
runLgRepository :: Repository -> LgRepository m a -> m aSource
strToOid :: String -> IO (ForeignPtr C'git_oid)Source
withLibGitDo :: IO a -> IO a