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

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.Rebase.Container

Synopsis

Documentation

data Suspended p wX wY where Source #

A patch that lives in a repository where a rebase is in progress. Such a repository will consist of Normal patches along with exactly one Suspended patch.

Most rebase operations will require the Suspended patch to be at the end of the repository.

Normal represents a normal patch within a respository where a rebase is in progress. Normal p is given the same on-disk representation as p, so a repository can be switched into and out of rebasing mode simply by adding or removing a Suspended patch and setting the appropriate format flag.

The single Suspended patch contains the entire rebase state, in the form of RebaseItems.

Note that the witnesses are such that the Suspended patch has no effect on the context of the rest of the repository; in a sense the patches within it are dangling off to one side from the main repository.

See Note [Rebase representation] in the Rebase for a discussion of the design choice to embed the rebase state in a single patch.

Constructors

Items :: FL (RebaseItem p) wX wY -> Suspended p wX wX 
Instances
(Show2 p, Show2 (PrimOf p)) => Show2 (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

Methods

showDict2 :: ShowDict (Suspended p wX wY) Source #

(PrimPatchBase p, PatchInspect p) => PatchInspect (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

(PrimPatchBase p, PatchListFormat p, ReadPatch p) => ReadPatch (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

Methods

readPatch' :: ParserM m => m (Sealed (Suspended p wX)) Source #

Apply (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

Associated Types

type ApplyState (Suspended p) :: (Type -> Type) -> Type Source #

Methods

apply :: ApplyMonad (ApplyState (Suspended p)) m => Suspended p wX wY -> m () Source #

(PrimPatchBase p, PatchListFormat p, Apply p, CommuteNoConflicts p, Conflict p, IsHunk p, ShowPatch p) => ShowPatch (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

Methods

showNicely :: Suspended p wX wY -> Doc Source #

description :: Suspended p wX wY -> Doc Source #

summary :: Suspended p wX wY -> Doc Source #

summaryFL :: FL (Suspended p) wX wY -> Doc Source #

thing :: Suspended p wX wY -> String Source #

things :: Suspended p wX wY -> String Source #

(PrimPatchBase p, PatchListFormat p, ShowPatchBasic p) => ShowPatchBasic (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

Methods

showPatch :: ShowPatchFor -> Suspended p wX wY -> Doc Source #

RepairToFL (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

Methods

applyAndTryToFixFL :: ApplyMonad (ApplyState (Suspended p)) m => Suspended p wX wY -> m (Maybe (String, FL (Suspended p) wX wY)) Source #

Repair (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

Methods

applyAndTryToFix :: ApplyMonad (ApplyState (Suspended p)) m => Suspended p wX wY -> m (Maybe (String, Suspended p wX wY)) Source #

Check p => Check (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

Methods

isInconsistent :: Suspended p wX wY -> Maybe Doc Source #

PrimPatchBase p => PrimPatchBase (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

Associated Types

type PrimOf (Suspended p) :: Type -> Type -> Type Source #

Effect (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

Methods

effect :: Suspended p wX wY -> FL (PrimOf (Suspended p)) wX wY Source #

effectRL :: Suspended p wX wY -> RL (PrimOf (Suspended p)) wX wY Source #

Conflict p => Conflict (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

(Show2 p, Show2 (PrimOf p)) => Show1 (Suspended p wX) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

Methods

showDict1 :: ShowDict (Suspended p wX wX0) Source #

(Show2 p, Show2 (PrimOf p)) => Show (Suspended p wX wY) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

Methods

showsPrec :: Int -> Suspended p wX wY -> ShowS #

show :: Suspended p wX wY -> String #

showList :: [Suspended p wX wY] -> ShowS #

type ApplyState (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

type PrimOf (Suspended p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Container

type PrimOf (Suspended p) = PrimOf p

addFixupsToSuspended :: (PrimPatchBase p, Commute p, FromPrim p, Effect p) => Named p wX wY -> Suspended p wY wY -> Suspended p wX wX Source #

add fixups for the name and effect of a patch to a Suspended

removeFixupsFromSuspended :: (PrimPatchBase p, Commute p, FromPrim p, Effect p) => Named p wX wY -> Suspended p wX wX -> Suspended p wY wY Source #

remove fixups (actually, add their inverse) for the name and effect of a patch to a Suspended