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.
- newtype LgRepository m a = LgRepository {
- lgRepositoryReaderT :: ReaderT Repository m a
- type BlobOid m = BlobOid (LgRepository m)
- type Commit m = Commit (LgRepository m)
- type CommitOid m = CommitOid (LgRepository m)
- type family Oid m1 :: *
- data OidPtr = OidPtr {}
- mkOid :: ForeignPtr C'git_oid -> OidPtr
- data Repository = Repository {}
- type Tree m = Tree (LgRepository m)
- type TreeOid m = TreeOid (LgRepository m)
- repoPath :: Repository -> FilePath
- addTracingBackend :: MonadGit m => LgRepository m ()
- checkResult :: (Eq a, Num a, Failure GitException m) => a -> Text -> m ()
- closeLgRepository :: MonadGit m => Repository -> m ()
- defaultLgOptions :: RepositoryOptions
- lgBuildPackIndex :: FilePath -> ByteString -> IO (Text, FilePath, FilePath)
- lgFactory :: MonadGit m => RepositoryFactory LgRepository m Repository
- lgForEachObject :: Ptr C'git_odb -> (Ptr C'git_oid -> Ptr () -> IO CInt) -> Ptr () -> IO CInt
- lgGet :: Monad m => LgRepository m Repository
- lgExcTrap :: Monad m => LgRepository m (IORef (Maybe GitException))
- lgLoadPackFileInMemory :: FilePath -> Ptr (Ptr C'git_odb_backend) -> Ptr (Ptr C'git_odb) -> ResourceT IO (Ptr C'git_odb)
- lgBuildPackFile :: MonadGit m => FilePath -> [Either (CommitOid m) (TreeOid m)] -> LgRepository m FilePath
- lgReadFromPack :: FilePath -> SHA -> Bool -> IO (Maybe (C'git_otype, CSize, ByteString))
- lgWithPackFile :: FilePath -> (Ptr C'git_odb -> ResourceT IO a) -> IO a
- lgCopyPackFile :: MonadGit m => FilePath -> LgRepository m ()
- lgWrap :: (MonadIO m, MonadBaseControl IO m) => LgRepository m a -> LgRepository m a
- oidToSha :: Ptr C'git_oid -> IO SHA
- shaToOid :: SHA -> IO (ForeignPtr C'git_oid)
- openLgRepository :: MonadGit m => RepositoryOptions -> m Repository
- runLgRepository :: Repository -> LgRepository m a -> m a
- strToOid :: String -> IO (ForeignPtr C'git_oid)
- withLibGitDo :: IO a -> IO a
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 family Oid m1 :: *
Constructors
OidPtr | |
Fields |
mkOid :: ForeignPtr C'git_oid -> OidPtrSource
type Tree m = Tree (LgRepository m)Source
type TreeOid m = TreeOid (LgRepository m)Source
repoPath :: Repository -> FilePathSource
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
lgBuildPackFile :: MonadGit m => FilePath -> [Either (CommitOid m) (TreeOid m)] -> LgRepository m FilePathSource
lgReadFromPack :: FilePath -> SHA -> Bool -> IO (Maybe (C'git_otype, CSize, ByteString))Source
lgCopyPackFile :: MonadGit m => FilePath -> LgRepository m ()Source
lgWrap :: (MonadIO m, MonadBaseControl IO m) => LgRepository m a -> LgRepository m aSource
openLgRepository :: MonadGit m => RepositoryOptions -> m RepositorySource
runLgRepository :: Repository -> LgRepository m a -> m aSource
withLibGitDo :: IO a -> IO a
Write an IO action so that proper initialization and shutdown of the thread libgit2 library is performed.