Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data RepoJob a
- = RepoJob (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO a)
- | V1Job (forall wR wU. Repository ('RepoType 'NoRebase) (RepoPatchV1 Prim) wR wU wR -> IO a)
- | V2Job (forall rt wR wU. IsRepoType rt => Repository rt (RepoPatchV2 Prim) wR wU wR -> IO a)
- | PrimV1Job (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree, IsPrimV1 (PrimOf p)) => Repository rt p wR wU wR -> IO a)
- | RebaseAwareJob (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO a)
- | RebaseJob (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'IsRebase) p wR wU wR -> IO a)
- | OldRebaseJob (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'IsRebase) p wR wU wR -> IO a)
- | StartRebaseJob (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'IsRebase) p wR wU wR -> IO a)
- class ApplyState p ~ Tree => IsPrimV1 p where
- withRepoLock :: DryRun -> UseCache -> UpdatePending -> UMask -> RepoJob a -> IO a
- withOldRepoLock :: RepoJob a -> IO a
- withRepoLockCanFail :: UseCache -> RepoJob () -> IO ()
- withRepository :: UseCache -> RepoJob a -> IO a
- withRepositoryLocation :: UseCache -> String -> RepoJob a -> IO a
- checkRepoIsNoRebase :: forall rt p wR wU wT. IsRepoType rt => Repository rt p wR wU wT -> Maybe (Repository ('RepoType 'NoRebase) p wR wU wT)
- withUMaskFlag :: UMask -> IO a -> IO a
Documentation
A RepoJob
wraps up an action to be performed with a repository. Because repositories
can contain different types of patches, such actions typically need to be polymorphic
in the kind of patch they work on. RepoJob
is used to wrap up the polymorphism,
and the various functions that act on a RepoJob
are responsible for instantiating
the underlying action with the appropriate patch type.
RepoJob (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO a) | The most common |
V1Job (forall wR wU. Repository ('RepoType 'NoRebase) (RepoPatchV1 Prim) wR wU wR -> IO a) | A job that only works on darcs 1 patches |
V2Job (forall rt wR wU. IsRepoType rt => Repository rt (RepoPatchV2 Prim) wR wU wR -> IO a) | A job that only works on darcs 2 patches |
PrimV1Job (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree, IsPrimV1 (PrimOf p)) => Repository rt p wR wU wR -> IO a) | A job that works on any repository where the patch type This was added to support darcsden, which inspects the internals of V1 prim patches. In future this should be replaced with a more abstract inspection API as part of |
RebaseAwareJob (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO a) | |
RebaseJob (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'IsRebase) p wR wU wR -> IO a) | |
OldRebaseJob (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'IsRebase) p wR wU wR -> IO a) | |
StartRebaseJob (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'IsRebase) p wR wU wR -> IO a) |
class ApplyState p ~ Tree => IsPrimV1 p where Source #
withRepoLock :: DryRun -> UseCache -> UpdatePending -> UMask -> RepoJob a -> IO a Source #
Apply a given RepoJob to a repository in the current working directory. However, before doing the job, take the repo lock and initializes a repo transaction, unless this is a dry-run.
withOldRepoLock :: RepoJob a -> IO a Source #
run a lock-taking job in an old-fashion repository. only used by `darcs optimize upgrade`.
withRepoLockCanFail :: UseCache -> RepoJob () -> IO () Source #
Apply a given RepoJob to a repository in the current working directory, taking a lock. If lock not takeable, do nothing. If old-fashioned repository, do nothing. The job must not touch pending or pending.tentative, because there is no call to revertRepositoryChanges. This entry point is currently only used for attemptCreatePatchIndex.
withRepository :: UseCache -> RepoJob a -> IO a Source #
apply a given RepoJob to a repository in the current working directory
withRepositoryLocation :: UseCache -> String -> RepoJob a -> IO a Source #
apply a given RepoJob to a repository in a given url
checkRepoIsNoRebase :: forall rt p wR wU wT. IsRepoType rt => Repository rt p wR wU wT -> Maybe (Repository ('RepoType 'NoRebase) p wR wU wT) Source #