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

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.Rebase.Change

Synopsis

Documentation

data RebaseChange prim wX wY where Source #

Constructors

RC :: FL (RebaseFixup prim) wX wY -> Named prim wY wZ -> RebaseChange prim wX wZ 
Instances
PatchListFormat (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Show2 prim => Show2 (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Methods

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

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

Defined in Darcs.Patch.Rebase.Change

Methods

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

Commute prim => Commute (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Methods

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

PatchInspect prim => PatchInspect (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Apply prim => Apply (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Associated Types

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

Methods

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

unapply :: ApplyMonad (ApplyState (RebaseChange prim)) m => RebaseChange prim wX wY -> m () Source #

PrimPatch prim => ShowPatch (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Methods

content :: RebaseChange prim wX wY -> Doc Source #

description :: RebaseChange prim wX wY -> Doc Source #

summary :: RebaseChange prim wX wY -> Doc Source #

summaryFL :: FL (RebaseChange prim) wX wY -> Doc Source #

thing :: RebaseChange prim wX wY -> String Source #

things :: RebaseChange prim wX wY -> String Source #

(ShowPatchBasic prim, Invert prim, PatchListFormat prim) => ShowContextPatch (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

(ShowPatchBasic prim, Invert prim, PatchListFormat prim) => ShowPatchBasic (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Methods

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

Ident (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Methods

ident :: RebaseChange prim wX wY -> PatchId (RebaseChange prim) Source #

IsHunk (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Methods

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

(ReadPatch prim, PatchListFormat prim) => ReadPatch (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

PrimPatch prim => PrimPatchBase (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Associated Types

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

Commute prim => Summary (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

HasDeps (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Methods

getdeps :: RebaseChange prim wX wY -> [PatchInfo] Source #

Show2 prim => Show1 (RebaseChange prim wX) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Methods

showDict1 :: Dict (Show (RebaseChange prim wX wX0)) Source #

Show2 prim => Show (RebaseChange prim wX wY) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Methods

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

show :: RebaseChange prim wX wY -> String #

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

type ApplyState (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

type PatchId (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

type PrimOf (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

type PrimOf (RebaseChange prim) = prim

extractRebaseChange :: forall p wX wY. RepoPatch p => DiffAlgorithm -> FL (RebaseChange (PrimOf p)) wX wY -> (FL (WDDNamed p) :> FL (RebaseFixup (PrimOf 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.

reifyRebaseChange :: FromPrim p => String -> FL (RebaseChange (PrimOf p)) wX wY -> IO ((FL (WDDNamed p) :> FL (RebaseFixup (PrimOf p))) wX wY) Source #

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

partitionUnconflicted :: Commute prim => FL (RebaseChange prim) wX wY -> (FL (RebaseChange prim) :> RL (RebaseChange prim)) wX wY Source #

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

rcToPia :: RebaseChange prim wX wY -> Sealed2 (PatchInfoAnd (RepoType NoRebase) prim) Source #

Get hold of the Named patch inside a RebaseChange and wrap it in a PatchInfoAnd.

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

Associated Types

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

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

Defined in Darcs.Patch.Rebase.Change

Methods

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

type PrimOf (WithDroppedDeps p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

simplifyPush :: PrimPatch prim => DiffAlgorithm -> RebaseFixup prim wX wY -> FL (RebaseChange prim) wY wZ -> Sealed (FL (RebaseChange prim) wX) Source #

Given a list of rebase items, try to push a new fixup as far as possible into the list as possible, using both commutation and coalescing. If the fixup commutes past all the ToEdit patches then it is dropped entirely.

simplifyPushes :: PrimPatch prim => DiffAlgorithm -> FL (RebaseFixup prim) wX wY -> FL (RebaseChange prim) wY wZ -> Sealed (FL (RebaseChange prim) wX) Source #

Like simplifyPush but for a list of fixups.