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

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.V2.RepoPatch

Synopsis

Documentation

data RepoPatchV2 prim wX wY where Source #

RepoPatchV2 is used to represents prim patches that are duplicates of, or conflict with, another prim patch in the repository.

Normal prim: A primitive patch

Duplicate x: This patch has no effect since x is already present in the repository.

Etacilpud x: invert (Duplicate x)

Conflictor ix xx x: ix is the set of patches: * that conflict with x and also conflict with another patch in the repository. * that conflict with a patch that conflict with x

xx is the sequence of patches that conflict *only* with x

x is the original, conflicting patch.

ix and x are stored as Non objects, which include any necessary context to uniquely define the patch that is referred to.

The intuition is that a Conflictor should have the effect of inverting any patches that x conflicts with, that haven't already been undone by another Conflictor in the repository. Therefore, the effect of a Conflictor is invert xx.

InvConflictor ix xx x: like invert (Conflictor ix xx x)

Constructors

Duplicate :: Non (RepoPatchV2 prim) wX -> RepoPatchV2 prim wX wX 
Etacilpud :: Non (RepoPatchV2 prim) wX -> RepoPatchV2 prim wX wX 
Normal :: prim wX wY -> RepoPatchV2 prim wX wY 
Conflictor :: [Non (RepoPatchV2 prim) wX] -> FL prim wX wY -> Non (RepoPatchV2 prim) wX -> RepoPatchV2 prim wY wX 
InvConflictor :: [Non (RepoPatchV2 prim) wX] -> FL prim wX wY -> Non (RepoPatchV2 prim) wX -> RepoPatchV2 prim wX wY 
Instances
PatchListFormat (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

PrimPatch prim => Eq2 (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

unsafeCompare :: RepoPatchV2 prim wA wB -> RepoPatchV2 prim wC wD -> Bool Source #

(=\/=) :: RepoPatchV2 prim wA wB -> RepoPatchV2 prim wA wC -> EqCheck wB wC Source #

(=/\=) :: RepoPatchV2 prim wA wC -> RepoPatchV2 prim wB wC -> EqCheck wA wB Source #

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

Defined in Darcs.Patch.V2.RepoPatch

Methods

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

Invert prim => Invert (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

invert :: RepoPatchV2 prim wX wY -> RepoPatchV2 prim wY wX Source #

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

Defined in Darcs.Patch.V2.RepoPatch

Methods

listTouchedFiles :: RepoPatchV2 prim wX wY -> [FilePath] Source #

hunkMatches :: (ByteString -> Bool) -> RepoPatchV2 prim wX wY -> Bool Source #

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

Defined in Darcs.Patch.V2.RepoPatch

Methods

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

PrimPatch prim => Commute (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

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

PrimPatch prim => Merge (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

merge :: (RepoPatchV2 prim :\/: RepoPatchV2 prim) wX wY -> (RepoPatchV2 prim :/\: RepoPatchV2 prim) wX wY Source #

PrimPatch prim => ReadPatch (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

readPatch' :: ParserM m => m (Sealed (RepoPatchV2 prim wX)) Source #

PrimPatch prim => Apply (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Associated Types

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

Methods

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

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

Defined in Darcs.Patch.V2.RepoPatch

Methods

showNicely :: RepoPatchV2 prim wX wY -> Doc Source #

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

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

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

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

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

PrimPatch prim => ShowContextPatch (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

PrimPatch prim => ShowPatchBasic (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

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

IsHunk prim => IsHunk (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

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

PrimPatch prim => RepairToFL (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

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

PrimPatch prim => Check (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

isInconsistent :: RepoPatchV2 prim wX wY -> Maybe Doc Source #

ToFromPrim (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

toPrim :: RepoPatchV2 prim wX wY -> Maybe (PrimOf (RepoPatchV2 prim) wX wY) Source #

FromPrim (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

fromPrim :: PrimOf (RepoPatchV2 prim) wX wY -> RepoPatchV2 prim wX wY Source #

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

Defined in Darcs.Patch.V2.RepoPatch

Associated Types

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

PrimPatch prim => Effect (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

effect :: RepoPatchV2 prim wX wY -> FL (PrimOf (RepoPatchV2 prim)) wX wY Source #

effectRL :: RepoPatchV2 prim wX wY -> RL (PrimOf (RepoPatchV2 prim)) wX wY Source #

PrimPatch prim => Nonable (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

non :: RepoPatchV2 prim wX wY -> Non (RepoPatchV2 prim) wX Source #

PrimPatch prim => CommuteNoConflicts (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

commuteNoConflicts :: (RepoPatchV2 prim :> RepoPatchV2 prim) wX wY -> Maybe ((RepoPatchV2 prim :> RepoPatchV2 prim) wX wY) Source #

PrimPatch prim => Conflict (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

PrimPatch prim => Matchable (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2

(PrimPatch prim, Annotate prim) => Annotate (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

annotate :: RepoPatchV2 prim wX wY -> AnnotatedM () Source #

(PrimPatch prim, Annotate prim) => RepoPatch (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2

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

Defined in Darcs.Patch.V2.RepoPatch

Methods

showDict1 :: ShowDict (RepoPatchV2 prim wX wX0) Source #

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

Defined in Darcs.Patch.V2.RepoPatch

Methods

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

show :: RepoPatchV2 prim wX wY -> String #

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

type ApplyState (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

type ApplyState (RepoPatchV2 prim) = ApplyState prim
type PrimOf (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

type PrimOf (RepoPatchV2 prim) = prim

isConsistent :: PrimPatch prim => RepoPatchV2 prim wX wY -> Maybe Doc Source #

This is used for unit-testing and for internal sanity checks

isForward :: PrimPatch prim => RepoPatchV2 prim wS wY -> Maybe Doc Source #

isForward p is True if p is either an InvConflictor or Etacilpud.

isDuplicate :: RepoPatchV2 prim wS wY -> Bool Source #

isDuplicate p is True if p is either a Duplicate or Etacilpud patch.

mergeUnravelled :: PrimPatch prim => [Sealed (FL prim wX)] -> Maybe (FlippedSeal (RepoPatchV2 prim) wX) Source #

mergeUnravelled is used when converting from Darcs V1 patches (Mergers) to Darcs V2 patches (Conflictors).