Safe Haskell | None |
---|---|
Language | Haskell98 |
Git.Libgit2
Contents
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
type MonadLg m = (Applicative m, MonadExcept m, MonadUnliftIO m) Source #
class HasLgRepo m where Source #
Minimal complete definition
Methods
getRepository :: m LgRepo Source #
Constructors
LgRepo | |
Fields |
Instances
lgRepoPath :: LgRepo -> FilePath Source #
addTracingBackend :: LgRepo -> IO () Source #
checkResult :: (Eq a, Num a, MonadExcept m) => a -> Text -> m () Source #
lgBuildPackIndex :: MonadUnliftIO m => FilePath -> ByteString -> m (Text, FilePath, FilePath) Source #
lgForEachObject :: Ptr C'git_odb -> (Ptr C'git_oid -> Ptr () -> IO CInt) -> Ptr () -> IO CInt Source #
lgBuildPackFile :: MonadLg m => FilePath -> [Either CommitOid TreeOid] -> ReaderT LgRepo m FilePath Source #
lgReadFromPack :: (MonadIO m, MonadExcept m) => Ptr C'git_odb -> SHA -> Bool -> m (Maybe (C'git_otype, CSize, ByteString)) Source #
lgOpenPackFile :: (MonadExcept m, MonadUnliftIO m) => FilePath -> m (Ptr C'git_odb) Source #
lgClosePackFile :: (MonadIO m, MonadExcept m) => Ptr C'git_odb -> m () Source #
lgWithPackFile :: (MonadExcept m, MonadUnliftIO m) => FilePath -> (Ptr C'git_odb -> m a) -> m a Source #
lgDiffContentsWithTree :: MonadLg m => Source (ReaderT LgRepo m) (Either TreeFilePath (Either SHA ByteString)) -> Tree -> Producer (ReaderT LgRepo m) ByteString Source #
openLgRepository :: (MonadIO m, MonadMask m) => RepositoryOptions -> m LgRepo Source #