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

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.Rebase.Viewing

Synopsis

Documentation

data RebaseSelect p wX wY where Source #

Encapsulate a single patch in the rebase state together with its fixups. Used during interactive selection to make sure that each item presented to the user corresponds to a patch.

Constructors

RSFwd :: FL (RebaseFixup p) wX wY -> Named p wY wZ -> RebaseSelect p wX wZ 
RSRev :: FL (RebaseFixup p) wX wY -> Named p wY wZ -> RebaseSelect p wZ wX 
Instances
(PrimPatchBase p, Commute p, Eq2 p) => Eq2 (RebaseSelect p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

unsafeCompare :: RebaseSelect p wA wB -> RebaseSelect p wC wD -> Bool Source #

(=\/=) :: RebaseSelect p wA wB -> RebaseSelect p wA wC -> EqCheck wB wC Source #

(=/\=) :: RebaseSelect p wA wC -> RebaseSelect p wB wC -> EqCheck wA wB Source #

(Show2 p, Show2 (PrimOf p)) => Show2 (RebaseSelect p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

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

Invert (RebaseSelect p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

invert :: RebaseSelect p wX wY -> RebaseSelect p wY wX Source #

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

Defined in Darcs.Patch.Rebase.Viewing

PatchDebug p => PatchDebug (RebaseSelect p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

patchDebugDummy :: RebaseSelect p wX wY -> () Source #

(PrimPatchBase p, FromPrim p, Effect p, Commute p, Invert p) => Commute (RebaseSelect p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

commute :: (RebaseSelect p :> RebaseSelect p) wX wY -> Maybe ((RebaseSelect p :> RebaseSelect p) wX wY) Source #

ReadPatch (RebaseSelect p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

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

(PrimPatchBase p, Invert p, Apply p, ApplyState p ~ ApplyState (PrimOf p)) => Apply (RebaseSelect p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Associated Types

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

Methods

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

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

Defined in Darcs.Patch.Rebase.Viewing

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

Defined in Darcs.Patch.Rebase.Viewing

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

Defined in Darcs.Patch.Rebase.Viewing

Methods

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

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

Defined in Darcs.Patch.Rebase.Viewing

Associated Types

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

(PrimPatchBase p, Invert p, Effect p) => Effect (RebaseSelect p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

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

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

(PrimPatchBase p, Conflict p, CommuteNoConflicts p, Invert p) => Conflict (RebaseSelect p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

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

Defined in Darcs.Patch.Rebase.Viewing

Methods

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

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

Defined in Darcs.Patch.Rebase.Viewing

Methods

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

show :: RebaseSelect p wX wY -> String #

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

type ApplyState (RebaseSelect p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

type PrimOf (RebaseSelect p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

toRebaseSelect :: PrimPatchBase p => FL (RebaseItem p) wX wY -> FL (RebaseSelect p) wX wY Source #

Turn a list of rebase items being rebased into a list suitable for use by interactive selection. Each actual patch being rebased is grouped together with any fixups needed.

fromRebaseSelect :: FL (RebaseSelect p) wX wY -> FL (RebaseItem p) wX wY Source #

Turn a list of items back from the format used for interactive selection into a normal list

extractRebaseSelect :: (Merge p, Invert p, Effect p, FromPrim p, PrimPatchBase p) => FL (RebaseSelect p) wX wY -> (FL (WDDNamed p) :> FL (RebaseFixup p)) wX wY Source #

Turn a selected rebase patch back into a patch we can apply to the main repository, together with residual fixups that need to go back into the rebase state (unless the rebase is now finished). Any fixups associated with the patch will turn into conflicts.

reifyRebaseSelect :: forall p wX wY. (PrimPatchBase p, FromPrim p) => FL (RebaseSelect p) wX wY -> IO ((FL (WDDNamed p) :> FL (RebaseFixup p)) wX wY) Source #

Like extractRebaseSelect, but any fixups are "reified" into a separate patch.

partitionUnconflicted :: (PrimPatchBase p, FromPrim p, Effect p, Commute p, Invert p) => FL (RebaseSelect p) wX wY -> (FL (RebaseSelect p) :> RL (RebaseSelect p)) wX wY Source #

Split a list of rebase patches into those that will have conflicts if unsuspended and those that won't.

rsToPia :: RebaseSelect p wX wY -> Sealed2 (PatchInfoAnd (RepoType NoRebase) p) Source #

Get hold of the PatchInfoAnd patch inside a RebaseSelect.

data WithDroppedDeps p wX wY Source #

A patch, together with a list of patch names that it used to depend on, but were lost during the rebasing process. The UI can use this information to report them to the user.

Constructors

WithDroppedDeps 

Fields

Instances
PrimPatchBase p => PrimPatchBase (WithDroppedDeps p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Associated Types

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

Effect p => Effect (WithDroppedDeps p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

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

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

type PrimOf (WithDroppedDeps p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

data RebaseChange p wX wY where Source #

Used for displaying during 'rebase changes'. 'Named (RebaseChange p)' is very similar to 'RebaseSelect p' but slight mismatches (Named embeds an FL) makes it not completely trivial to merge them.

Constructors

RCFwd :: FL (RebaseFixup p) wX wY -> FL p wY wZ -> RebaseChange p wX wZ 
RCRev :: FL (RebaseFixup p) wX wY -> FL p wY wZ -> RebaseChange p wZ wX 
Instances
PatchListFormat (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

(Show2 p, Show2 (PrimOf p)) => Show2 (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

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

Invert (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

invert :: RebaseChange p wX wY -> RebaseChange p wY wX Source #

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

Defined in Darcs.Patch.Rebase.Viewing

PatchDebug p => PatchDebug (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

patchDebugDummy :: RebaseChange p wX wY -> () Source #

Commute (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

commute :: (RebaseChange p :> RebaseChange p) wX wY -> Maybe ((RebaseChange p :> RebaseChange p) wX wY) Source #

ReadPatch (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

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

(PrimPatchBase p, Invert p, Apply p, ApplyState p ~ ApplyState (PrimOf p)) => Apply (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Associated Types

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

Methods

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

(PrimPatchBase p, PatchListFormat p, ShowPatchBasic p, Invert p, Effect p, Merge p, FromPrim p, Conflict p, CommuteNoConflicts p) => ShowPatch (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

(PrimPatchBase p, ShowPatchBasic p) => ShowContextPatch (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

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

Defined in Darcs.Patch.Rebase.Viewing

Methods

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

IsHunk (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

isHunk :: RebaseChange p wX wY -> Maybe (FileHunk wX wY) Source #

PrimPatch (PrimOf p) => PrimPatchBase (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Associated Types

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

(PrimPatchBase p, Invert p, Effect p) => Effect (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

Methods

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

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

CommuteNoConflicts (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

(PrimPatchBase p, Invert p, Effect p, FromPrim p, Merge p, Conflict p, CommuteNoConflicts p) => Conflict (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

(PrimPatchBase p, Apply p, Invert p, PatchInspect p, ApplyState p ~ ApplyState (PrimOf p)) => Matchable (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

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

Defined in Darcs.Patch.Rebase.Viewing

Methods

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

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

Defined in Darcs.Patch.Rebase.Viewing

Methods

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

show :: RebaseChange p wX wY -> String #

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

type ApplyState (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing

type PrimOf (RebaseChange p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Viewing