darcs-2.14.4: a distributed, interactive, smart revision control system

Safe HaskellNone
LanguageHaskell2010

Darcs.Repository.Job

Synopsis

Documentation

data RepoJob a Source #

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.

Constructors

RepoJob (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO a)

The most common RepoJob; the underlying action can accept any patch type that a darcs repository may use.

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 p has PrimOf p = Prim.

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 PrimPatch.

RebaseAwareJob RebaseJobFlags (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO a) 
RebaseJob RebaseJobFlags (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => Repository (RepoType IsRebase) p wR wU wR -> IO a) 
StartRebaseJob RebaseJobFlags (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 #

Methods

toPrimV1 :: p wX wY -> Prim wX wY Source #

Instances
IsPrimV1 Prim Source # 
Instance details

Defined in Darcs.Repository.Job

Methods

toPrimV1 :: Prim wX wY -> Prim0 wX wY Source #

IsPrimV1 Prim Source # 
Instance details

Defined in Darcs.Repository.Job

Methods

toPrimV1 :: Prim wX wY -> Prim0 wX wY Source #

withRepoLock :: DryRun -> UseCache -> UpdateWorking -> UMask -> RepoJob a -> IO a Source #

apply a given RepoJob to a repository in the current working directory, taking a lock

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 #

If the RepoType of the given repo indicates that we have NoRebase, then Just the repo with the refined type, else Nothing. NB The amount of types we have to import to make this simple check is ridiculous!