darcs-beta-2.7.99.1: a distributed, interactive, smart revision control system

Safe HaskellSafe-Infered

Darcs.Patch.Prim.Class

Documentation

class PrimConstruct prim whereSource

Methods

addfile :: FilePath -> prim x ySource

rmfile :: FilePath -> prim x ySource

adddir :: FilePath -> prim x ySource

rmdir :: FilePath -> prim x ySource

move :: FilePath -> FilePath -> prim x ySource

changepref :: String -> String -> String -> prim x ySource

hunk :: FilePath -> Int -> [ByteString] -> [ByteString] -> prim x ySource

tokreplace :: FilePath -> String -> String -> String -> prim x ySource

binary :: FilePath -> ByteString -> ByteString -> prim x ySource

primFromHunk :: FileHunk x y -> prim x ySource

anIdentity :: prim x xSource

class PrimCanonize prim whereSource

Methods

tryToShrink :: FL prim x y -> FL prim x ySource

tryShrinkingInverse :: FL prim x y -> Maybe (FL prim x y)Source

sortCoalesceFL :: FL prim x y -> FL prim x ySource

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

canonize :: prim x y -> FL prim x ySource

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 :: FL prim x y -> FL prim x ySource

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

join :: (prim :> prim) x y -> Maybe (FL prim x y)Source

class PrimClassify prim whereSource

Methods

primIsAddfile :: prim x y -> BoolSource

primIsRmfile :: prim x y -> BoolSource

primIsAdddir :: prim x y -> BoolSource

primIsRmdir :: prim x y -> BoolSource

primIsMove :: prim x y -> BoolSource

primIsHunk :: prim x y -> BoolSource

primIsTokReplace :: prim x y -> BoolSource

primIsBinary :: prim x y -> BoolSource

primIsSetpref :: prim x y -> BoolSource

is_filepatch :: prim x y -> Maybe FileNameSource

class PrimDetails prim whereSource

Methods

summarizePrim :: prim x y -> [SummDetail]Source

class PrimShow prim whereSource

Methods

showPrim :: FileNameFormat -> prim a b -> DocSource

showPrimFL :: PrimShow prim => FileNameFormat -> FL prim a b -> DocSource

class PrimRead prim whereSource

Methods

readPrim :: ParserM m => FileNameFormat -> m (Sealed (prim x))Source

class PrimApply prim whereSource

Methods

applyPrimFL :: ApplyMonad m (ApplyState prim) => FL prim x y -> m ()Source

class (Patchy prim, PatchListFormat prim, IsHunk prim, RepairToFL prim, PrimConstruct prim, PrimCanonize prim, PrimClassify prim, PrimDetails prim, PrimShow prim, PrimRead prim, PrimApply prim) => PrimPatch prim Source

class FromPrim p whereSource

Methods

fromPrim :: PrimOf p x y -> p x ySource

Instances

class FromPrims p whereSource

Methods

fromPrims :: FL (PrimOf p) x y -> p x ySource

joinPatches :: FL p x y -> p x ySource

Instances

FromPrim p => FromPrims (RL p) 
FromPrim p => FromPrims (FL p) 

class FromPrim p => ToFromPrim p whereSource

Methods

toPrim :: p x y -> Maybe (PrimOf p x y)Source

Instances