| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Darcs.Patch.Prim.Class
Documentation
class PrimConstruct prim where Source
Methods
addfile :: FilePath -> prim wX wY Source
rmfile :: FilePath -> prim wX wY Source
adddir :: FilePath -> prim wX wY Source
rmdir :: FilePath -> prim wX wY Source
move :: FilePath -> FilePath -> prim wX wY Source
changepref :: String -> String -> String -> prim wX wY Source
hunk :: FilePath -> Int -> [ByteString] -> [ByteString] -> prim wX wY Source
tokreplace :: FilePath -> String -> String -> String -> prim wX wY Source
binary :: FilePath -> ByteString -> ByteString -> prim wX wY Source
primFromHunk :: FileHunk wX wY -> prim wX wY Source
anIdentity :: prim wX wX Source
Instances
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?
tryShrinkingInverse :: FL prim wX wY -> Maybe (FL prim wX wY) Source
tryShrinkingInverse ps deletes the first subsequence of
   primitive patches that is followed by the inverse subsequence,
   if one exists.  If not, it returns Nothing
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
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 FileName Source
Instances
class PrimDetails prim where Source
Methods
summarizePrim :: prim wX wY -> [SummDetail] Source
showPrimFL :: PrimShow prim => FileNameFormat -> FL prim wA wB -> Doc Source
class PrimRead prim where Source
Methods
readPrim :: ParserM m => FileNameFormat -> m (Sealed (prim wX)) Source
class PrimApply prim where Source
Methods
applyPrimFL :: ApplyMonad m (ApplyState prim) => FL prim wX wY -> m () Source
class (Patchy prim, MyEq prim, PatchListFormat prim, IsHunk prim, RepairToFL prim, PatchInspect prim, ReadPatch prim, ShowPatch prim, PrimConstruct prim, PrimCanonize prim, PrimClassify prim, PrimDetails prim, PrimShow prim, PrimRead prim, PrimApply prim) => PrimPatch prim Source
class PrimPatch (PrimOf p) => PrimPatchBase p Source
Instances
| PrimPatchBase DummyPatch Source | |
| PrimPatchBase p => PrimPatchBase (RL p) Source | |
| PrimPatchBase p => PrimPatchBase (FL p) Source | |
| PrimPatchBase p => PrimPatchBase (Named p) Source | |
| PrimPatchBase p => PrimPatchBase (RebaseName p) Source | |
| PrimPatchBase p => PrimPatchBase (RebaseFixup p) Source | |
| PrimPatch prim => PrimPatchBase (Patch prim) Source | |
| PrimPatch prim => PrimPatchBase (RealPatch prim) Source | |
| PrimPatchBase p => PrimPatchBase (PatchInfoAnd p) Source | |
| PrimPatchBase p => PrimPatchBase (Rebasing p) Source | |
| PrimPatchBase p => PrimPatchBase (WithDroppedDeps p) Source | |
| PrimPatch (PrimOf p) => PrimPatchBase (RebaseChange p) Source | |
| PrimPatchBase p => PrimPatchBase (RebaseSelect p) Source | 
class FromPrim p => ToFromPrim p where Source
Instances
| ToFromPrim (RealPatch prim) Source |