darcs-2.18.2: a distributed, interactive, smart revision control system
Safe HaskellSafe-Inferred
LanguageHaskell2010

Darcs.UI.ApplyPatches

Synopsis

Documentation

class PatchApplier pa where Source #

This class is a hack to abstract over pullapply and rebase pullapply.

Methods

repoJob :: pa -> (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => PatchProxy p -> Repository 'RW p wU wR -> IO ()) -> RepoJob 'RW () Source #

applyPatches :: forall p wR wU wZ. (RepoPatch p, ApplyState p ~ Tree) => pa -> PatchProxy p -> String -> [DarcsFlag] -> Repository 'RW p wU wR -> Fork (PatchSet p) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wR wZ -> IO () Source #

Instances

Instances details
PatchApplier StandardPatchApplier Source # 
Instance details

Defined in Darcs.UI.ApplyPatches

Methods

repoJob :: StandardPatchApplier -> (forall (p :: Type -> Type -> Type) wR wU. (RepoPatch p, ApplyState p ~ Tree) => PatchProxy p -> Repository 'RW p wU wR -> IO ()) -> RepoJob 'RW () Source #

applyPatches :: forall (p :: Type -> Type -> Type) wR wU wZ. (RepoPatch p, ApplyState p ~ Tree) => StandardPatchApplier -> PatchProxy p -> String -> [DarcsFlag] -> Repository 'RW p wU wR -> Fork (PatchSet p) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wR wZ -> IO () Source #

data PatchProxy (p :: * -> * -> *) Source #

Constructors

PatchProxy 

data StandardPatchApplier Source #

Constructors

StandardPatchApplier 

Instances

Instances details
PatchApplier StandardPatchApplier Source # 
Instance details

Defined in Darcs.UI.ApplyPatches

Methods

repoJob :: StandardPatchApplier -> (forall (p :: Type -> Type -> Type) wR wU. (RepoPatch p, ApplyState p ~ Tree) => PatchProxy p -> Repository 'RW p wU wR -> IO ()) -> RepoJob 'RW () Source #

applyPatches :: forall (p :: Type -> Type -> Type) wR wU wZ. (RepoPatch p, ApplyState p ~ Tree) => StandardPatchApplier -> PatchProxy p -> String -> [DarcsFlag] -> Repository 'RW p wU wR -> Fork (PatchSet p) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wR wZ -> IO () Source #

applyPatchesFinish :: (RepoPatch p, ApplyState p ~ Tree) => String -> [DarcsFlag] -> Repository 'RW p wU wR -> FL (PrimOf p) wU wY -> Bool -> IO () Source #