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

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.Prim

Synopsis

Documentation

class PrimApply prim where Source #

Methods

applyPrimFL :: ApplyMonad (ApplyState prim) m => FL prim wX wY -> m () Source #

Instances
PrimApply Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Apply

Methods

applyPrimFL :: ApplyMonad (ApplyState Prim) m => FL Prim wX wY -> m () Source #

PrimApply Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.FileUUID.Apply

Methods

applyPrimFL :: ApplyMonad (ApplyState Prim) m => FL Prim wX wY -> m () Source #

PrimApply Prim Source # 
Instance details

Defined in Darcs.Patch.V2.Prim

Methods

applyPrimFL :: ApplyMonad (ApplyState Prim) m => FL Prim wX wY -> m () Source #

PrimApply Prim Source # 
Instance details

Defined in Darcs.Patch.V1.Prim

Methods

applyPrimFL :: ApplyMonad (ApplyState Prim) m => FL Prim wX wY -> m () Source #

PrimApply p => PrimApply (PrimWithName name p) Source # 
Instance details

Defined in Darcs.Patch.Prim.WithName

Methods

applyPrimFL :: ApplyMonad (ApplyState (PrimWithName name p)) m => FL (PrimWithName name p) wX wY -> m () Source #

class PrimCanonize prim where Source #

Methods

tryToShrink :: FL prim wX wY -> FL prim wX wY Source #

tryToShrink ps simplifies ps by getting rid of self-cancellations or coalescing patches

Question (Eric Kow): what properties should this have? For example, the prim1 implementation only gets rid of the first self-cancellation it finds (as far as I can tell). Is that OK? Can we try harder?

sortCoalesceFL :: FL prim wX wY -> FL prim wX wY Source #

sortCoalesceFL ps coalesces as many patches in ps as possible, sorting the results in some standard order.

canonize :: DiffAlgorithm -> prim wX wY -> FL prim wX wY Source #

It can sometimes be handy to have a canonical representation of a given patch. We achieve this by defining a canonical form for each patch type, and a function canonize which takes a patch and puts it into canonical form. This routine is used by the diff function to create an optimal patch (based on an LCS algorithm) from a simple hunk describing the old and new version of a file.

canonizeFL :: DiffAlgorithm -> FL prim wX wY -> FL prim wX wY Source #

canonizeFL ps puts a sequence of primitive patches into canonical form. Even if the patches are just hunk patches, this is not necessarily the same set of results as you would get if you applied the sequence to a specific tree and recalculated a diff.

Note that this process does not preserve the commutation behaviour of the patches and is therefore not appropriate for use when working with already recorded patches (unless doing amend-record or the like).

coalesce :: (prim :> prim) wX wY -> Maybe (FL prim wX wY) Source #

Either primCoalesce or cancel inverses.

primCoalesce (p :> q) == Just r => apply r = apply p >> apply q
primCoalesce (p :> q) == Just r => lengthFL r < 2

primCoalesce :: prim wX wY -> prim wY wZ -> Maybe (prim wX wZ) Source #

Coalesce adjacent patches to one with the same effect.

apply (primCoalesce p q) == apply p >> apply q

primDecoalesce :: prim wX wZ -> prim wX wY -> Maybe (prim wY wZ) Source #

If primCoalesce is addition, then this is subtraction.

Just r == primCoalesce p q => primDecoalesce r p == Just q
Instances
PrimCanonize Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Coalesce

Methods

tryToShrink :: FL Prim wX wY -> FL Prim wX wY Source #

sortCoalesceFL :: FL Prim wX wY -> FL Prim wX wY Source #

canonize :: DiffAlgorithm -> Prim wX wY -> FL Prim wX wY Source #

canonizeFL :: DiffAlgorithm -> FL Prim wX wY -> FL Prim wX wY Source #

coalesce :: (Prim :> Prim) wX wY -> Maybe (FL Prim wX wY) Source #

primCoalesce :: Prim wX wY -> Prim wY wZ -> Maybe (Prim wX wZ) Source #

primDecoalesce :: Prim wX wZ -> Prim wX wY -> Maybe (Prim wY wZ) Source #

PrimCanonize Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.FileUUID.Coalesce

Methods

tryToShrink :: FL Prim wX wY -> FL Prim wX wY Source #

sortCoalesceFL :: FL Prim wX wY -> FL Prim wX wY Source #

canonize :: DiffAlgorithm -> Prim wX wY -> FL Prim wX wY Source #

canonizeFL :: DiffAlgorithm -> FL Prim wX wY -> FL Prim wX wY Source #

coalesce :: (Prim :> Prim) wX wY -> Maybe (FL Prim wX wY) Source #

primCoalesce :: Prim wX wY -> Prim wY wZ -> Maybe (Prim wX wZ) Source #

primDecoalesce :: Prim wX wZ -> Prim wX wY -> Maybe (Prim wY wZ) Source #

PrimCanonize Prim Source # 
Instance details

Defined in Darcs.Patch.V2.Prim

Methods

tryToShrink :: FL Prim wX wY -> FL Prim wX wY Source #

sortCoalesceFL :: FL Prim wX wY -> FL Prim wX wY Source #

canonize :: DiffAlgorithm -> Prim wX wY -> FL Prim wX wY Source #

canonizeFL :: DiffAlgorithm -> FL Prim wX wY -> FL Prim wX wY Source #

coalesce :: (Prim :> Prim) wX wY -> Maybe (FL Prim wX wY) Source #

primCoalesce :: Prim wX wY -> Prim wY wZ -> Maybe (Prim wX wZ) Source #

primDecoalesce :: Prim wX wZ -> Prim wX wY -> Maybe (Prim wY wZ) Source #

PrimCanonize Prim Source # 
Instance details

Defined in Darcs.Patch.V1.Prim

Methods

tryToShrink :: FL Prim wX wY -> FL Prim wX wY Source #

sortCoalesceFL :: FL Prim wX wY -> FL Prim wX wY Source #

canonize :: DiffAlgorithm -> Prim wX wY -> FL Prim wX wY Source #

canonizeFL :: DiffAlgorithm -> FL Prim wX wY -> FL Prim wX wY Source #

coalesce :: (Prim :> Prim) wX wY -> Maybe (FL Prim wX wY) Source #

primCoalesce :: Prim wX wY -> Prim wY wZ -> Maybe (Prim wX wZ) Source #

primDecoalesce :: Prim wX wZ -> Prim wX wY -> Maybe (Prim wY wZ) Source #

class PrimClassify prim where Source #

Methods

primIsAddfile :: prim wX wY -> Bool Source #

primIsRmfile :: prim wX wY -> Bool Source #

primIsAdddir :: prim wX wY -> Bool Source #

primIsRmdir :: prim wX wY -> Bool Source #

primIsMove :: prim wX wY -> Bool Source #

primIsHunk :: prim wX wY -> Bool Source #

primIsTokReplace :: prim wX wY -> Bool Source #

primIsBinary :: prim wX wY -> Bool Source #

primIsSetpref :: prim wX wY -> Bool Source #

is_filepatch :: prim wX wY -> Maybe AnchoredPath Source #

Instances
PrimClassify Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

PrimClassify Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.FileUUID.Core

PrimClassify Prim Source # 
Instance details

Defined in Darcs.Patch.V2.Prim

PrimClassify Prim Source # 
Instance details

Defined in Darcs.Patch.V1.Prim

PrimClassify p => PrimClassify (PrimWithName name p) Source # 
Instance details

Defined in Darcs.Patch.Prim.WithName

class PrimConstruct prim where Source #

Methods

addfile :: AnchoredPath -> prim wX wY Source #

rmfile :: AnchoredPath -> prim wX wY Source #

adddir :: AnchoredPath -> prim wX wY Source #

rmdir :: AnchoredPath -> prim wX wY Source #

move :: AnchoredPath -> AnchoredPath -> prim wX wY Source #

changepref :: String -> String -> String -> prim wX wY Source #

hunk :: AnchoredPath -> Int -> [ByteString] -> [ByteString] -> prim wX wY Source #

tokreplace :: AnchoredPath -> String -> String -> String -> prim wX wY Source #

binary :: AnchoredPath -> ByteString -> ByteString -> prim wX wY Source #

primFromHunk :: FileHunk wX wY -> prim wX wY Source #

Instances
PrimConstruct Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

PrimConstruct Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.FileUUID.Core

PrimConstruct Prim Source # 
Instance details

Defined in Darcs.Patch.V2.Prim

PrimConstruct Prim Source # 
Instance details

Defined in Darcs.Patch.V1.Prim

class PrimDetails prim where Source #

Methods

summarizePrim :: prim wX wY -> [SummDetail] Source #

Instances
PrimDetails Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Details

Methods

summarizePrim :: Prim wX wY -> [SummDetail] Source #

PrimDetails Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.FileUUID.Details

Methods

summarizePrim :: Prim wX wY -> [SummDetail] Source #

PrimDetails Prim Source # 
Instance details

Defined in Darcs.Patch.V2.Prim

Methods

summarizePrim :: Prim wX wY -> [SummDetail] Source #

PrimDetails Prim Source # 
Instance details

Defined in Darcs.Patch.V1.Prim

Methods

summarizePrim :: Prim wX wY -> [SummDetail] Source #

PrimDetails p => PrimDetails (PrimWithName name p) Source # 
Instance details

Defined in Darcs.Patch.Prim.WithName

Methods

summarizePrim :: PrimWithName name p wX wY -> [SummDetail] Source #

class PrimMangleUnravelled prim where Source #

Methods

mangleUnravelled :: Unravelled prim wX -> Maybe (Mangled prim wX) Source #

Mangle conflicting alternatives if possible.

type PrimPatch prim = (Apply prim, CleanMerge prim, Commute prim, Invert prim, Eq2 prim, IsHunk prim, PatchInspect prim, RepairToFL prim, Show2 prim, PrimConstruct prim, PrimCanonize prim, PrimClassify prim, PrimDetails prim, PrimApply prim, PrimSift prim, PrimMangleUnravelled prim, ReadPatch prim, ShowPatch prim, ShowContextPatch prim, PatchListFormat prim) Source #

class PrimRead prim where Source #

Methods

readPrim :: FileNameFormat -> Parser (Sealed (prim wX)) Source #

Instances
PrimRead Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Read

PrimRead Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.FileUUID.Read

class PrimShow prim where Source #

Methods

showPrim :: FileNameFormat -> prim wA wB -> Doc Source #

showPrimCtx :: ApplyMonad (ApplyState prim) m => FileNameFormat -> prim wA wB -> m Doc Source #

class PrimSift prim where Source #

Methods

siftForPending :: FL prim wX wY -> Sealed (FL prim wX) Source #

siftForPending ps simplifies the candidate pending patch ps through a combination of looking for self-cancellations (sequences of patches followed by their inverses), coalescing, and getting rid of any hunk/binary patches we can commute out the back

The visual image of sifting can be quite helpful here. We are repeatedly tapping (shrinking) the patch sequence and shaking it (sift). Whatever falls out is the pending we want to keep. We do this until the sequence looks about as clean as we can get it

Instances
PrimSift Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1

Methods

siftForPending :: FL Prim wX wY -> Sealed (FL Prim wX) Source #

PrimSift Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.FileUUID.Coalesce

Methods

siftForPending :: FL Prim wX wY -> Sealed (FL Prim wX) Source #

PrimSift Prim Source # 
Instance details

Defined in Darcs.Patch.V2.Prim

Methods

siftForPending :: FL Prim wX wY -> Sealed (FL Prim wX) Source #

PrimSift Prim Source # 
Instance details

Defined in Darcs.Patch.V1.Prim

Methods

siftForPending :: FL Prim wX wY -> Sealed (FL Prim wX) Source #

type Mangled prim wX = Sealed (FL prim wX) Source #

Result of mangling a single Unravelled.

type Unravelled prim wX = [Sealed (FL prim wX)] Source #

A list of conflicting alternatives. They form a connected component of the conflict graph i.e. one transitive conflict.