| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Git.Monad
Description
Functionality we're currently missing (an assuredly incomplete list):
.gittextfile (gitdir: some-path)- using $GIT_DIRECTORY
objectsinfoalternatesor $GIT_ALTERNATE_OBJECT_DIRECTORIES
Synopsis
- class Monad m => MonadGit m where
- data GitT m a
- type Git a = GitT IO a
- runGit :: RawFilePath -> Git a -> IO a
- runGitT :: MonadIO m => RawFilePath -> GitT m a -> m a
- initRepo :: Maybe RawFilePath -> IO ()
- repoPath :: (MonadIO m, InRepo a) => a -> GitT m RawFilePath
- findBlob :: MonadGit m => Sha1 -> m (Maybe Blob)
- findTag :: MonadGit m => Sha1 -> m (Maybe Tag)
- findTree :: MonadGit m => Sha1 -> m (Maybe Tree)
- findTreeish :: MonadGit m => Sha1 -> m (Maybe Tree)
- findCommit :: MonadGit m => Sha1 -> m (Maybe Commit)
- grepCommit :: MonadGit m => (Commit -> Bool) -> Sha1 -> m (Maybe Sha1)
- resolveSha :: (MonadFail m, MonadGit m) => Sha1 -> [PathComponent] -> m (Maybe Sha1)
- resolveBlob :: (MonadFail m, MonadGit m) => Sha1 -> [PathComponent] -> m (Maybe Blob)
- writeBlob :: MonadGit m => Blob -> m Sha1
- writeTree :: MonadGit m => Tree -> m Sha1
- writeCommit :: MonadGit m => Commit -> m Sha1
- writeTag :: MonadGit m => Tag -> m Sha1
- packing :: MonadIO m => PackingT (GitT m) a -> GitT m a
- readBranch :: MonadGit m => RefName -> m (Maybe Sha1)
- readHead :: MonadGit m => m (Maybe Sha1)
- writeBranch :: MonadIO m => RefName -> Sha1 -> GitT m ()
- writeHead :: MonadGit m => Ref -> m ()
- detachHead :: MonadGit m => Sha1 -> m ()
- listBranches :: MonadGit m => m (Set RefName)
- readPackedRefs :: MonadIO m => GitT m (Maybe [(Ref, Sha1)])
- peelRef :: MonadGit m => Ref -> m (Maybe Sha1)
- peeled :: MonadGit m => Ref -> m Ref
The Git Monad
class Monad m => MonadGit m where Source #
Monads that let you work with git repositories.
Minimal complete definition
lookupSha, writeObject, lookupRef, listRefs, writeRef, writeSymRef, registerPack
Methods
lookupSha :: Sha1 -> m (Maybe Object) Source #
Try to look up an object by its Sha1.
writeObject :: Object -> m Sha1 Source #
Write an Object to storage, returning its Sha1. We should have the law:
writeObject o >>= s -> flushObjects >> lookupSha s == return (Just o)
flushObjects :: m () Source #
Flush written Objects to disk. Defaults to a no-op.
lookupRef :: Ref -> m (Maybe Sha1) Source #
listRefs :: m (Map Ref (Maybe Sha1)) Source #
A Map from Refs to the Sha1s at which they point, optionally. An instance may choose
not to provide hashes for some Refs (e.g., only providing hashes for packed refs, but not
loose ones).
writeRef :: Ref -> Sha1 -> m () Source #
Write a symref from the first argument to the second.
registerPack :: PackFile -> m () Source #
Register a packfile with git so it knows to search it. Primarily a support function for PackingT, and perhaps should be seperated out.
Instances
A Git monad transformer that writes loose objects.
Instances
| MonadTrans GitT Source # | |
Defined in Data.Git.Internal.Types | |
| Monad m => MonadState GitConf (GitT m) Source # | |
| Monad m => Monad (GitT m) Source # | |
| Functor m => Functor (GitT m) Source # | |
| MonadFail m => MonadFail (GitT m) Source # | |
Defined in Data.Git.Internal.Types | |
| Monad m => Applicative (GitT m) Source # | |
| MonadIO m => MonadIO (GitT m) Source # | |
Defined in Data.Git.Internal.Types | |
| MonadCatch m => MonadCatch (GitT m) Source # | |
| MonadThrow m => MonadThrow (GitT m) Source # | |
Defined in Data.Git.Internal.Types | |
| MonadIO m => MonadGit (GitT m) Source # | A concrete |
Defined in Data.Git.Monad Methods lookupSha :: Sha1 -> GitT m (Maybe Object) Source # writeObject :: Object -> GitT m Sha1 Source # flushObjects :: GitT m () Source # lookupRef :: Ref -> GitT m (Maybe Sha1) Source # listRefs :: GitT m (Map Ref (Maybe Sha1)) Source # writeRef :: Ref -> Sha1 -> GitT m () Source # writeSymRef :: Ref -> Ref -> GitT m () Source # registerPack :: PackFile -> GitT m () Source # | |
runGitT :: MonadIO m => RawFilePath -> GitT m a -> m a Source #
Do some git computations in the given git directory.
Repository Management
repoPath :: (MonadIO m, InRepo a) => a -> GitT m RawFilePath Source #
The path of an object in the git directory
Object Reading
resolveSha :: (MonadFail m, MonadGit m) => Sha1 -> [PathComponent] -> m (Maybe Sha1) Source #
Given a Sha1 that refers to a tree-ish (see findTreeish) and a list of path components,
find the Sha1 of the object in the tree at that path.
resolveBlob :: (MonadFail m, MonadGit m) => Sha1 -> [PathComponent] -> m (Maybe Blob) Source #
As resolveSha, expecting a Blob at the given location.
Object Writing
Writing Packfiles
packing :: MonadIO m => PackingT (GitT m) a -> GitT m a Source #
Run a GitT computation, writing objects to a packfile instead of loose.
Currently objects are not findable until flushObjects is called.
Ref Handling
readBranch :: MonadGit m => RefName -> m (Maybe Sha1) Source #
Read a Sha1 out of a branch (in refsheads)
writeBranch :: MonadIO m => RefName -> Sha1 -> GitT m () Source #
Set a branch (in refsheads) to a particular Sha1.
detachHead :: MonadGit m => Sha1 -> m () Source #
Set HEAD to a specific Sha1. Leaves the repo in a "detached HEAD" state.
readPackedRefs :: MonadIO m => GitT m (Maybe [(Ref, Sha1)]) Source #
Read this repository's packed-refs file, if it's there.
NB: Loose refs have priority over packed refs, so if (for example) a branch exists both loose and packed in the repository and is associated with different hashes, it points to whatever the loose one says. *However*, this function intentionally does *not* honor that.