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

Safe HaskellSafe-Infered

Darcs.Patch

Synopsis

Documentation

data Named p x y Source

The Named type adds a patch info about a patch, that is a name.

NamedP info deps p represents patch p with name info. deps is a list of dependencies added at the named patch level, compared with the unnamed level (ie, dependencies added with darcs record --ask-deps).

class (MyEq p, Apply p, Commute p, PatchInspect p, ShowPatch p, ReadPatch p, Invert p) => Patchy p Source

Instances

Patchy Prim 
Patchy Prim 
Patchy DummyPatch 
(IsHunk p, PatchListFormat p, Patchy p) => Patchy (RL p) 
(IsHunk p, PatchListFormat p, Patchy p) => Patchy (FL p) 
PrimPatch prim => Patchy (Patch prim) 
(CommuteNoConflicts p, Conflict p, IsHunk p, PatchListFormat p, PrimPatchBase p, Patchy p, ~ ((* -> *) -> *) (ApplyState p) Tree) => Patchy (Named p) 
(RepoPatch p, ~ ((* -> *) -> *) (ApplyState p) Tree) => Patchy (PatchInfoAnd p) 
PrimPatch prim => Patchy (RealPatch prim) 

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

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

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

rmfile :: PrimConstruct prim => FilePath -> prim x ySource

addfile :: PrimConstruct prim => FilePath -> prim x ySource

rmdir :: PrimConstruct prim => FilePath -> prim x ySource

adddir :: PrimConstruct prim => FilePath -> prim x ySource

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

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

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

namepatch :: Patchy p => String -> String -> String -> [String] -> FL p x y -> IO (Named p x y)Source

anonymous :: Patchy p => FL p x y -> IO (Named p x y)Source

showContextPatch :: (ShowPatch p, Monad m, ApplyMonadTrans m (ApplyState p), ApplyMonad m (ApplyState p), Monad m) => p x y -> m DocSource

showContextPatch is used to add context to a patch, as diff -u does. Thus, it differs from showPatch only for hunks. It is used for instance before putting it into a bundle. As this unified context is not included in patch representation, this requires access to the tree.

showNicely :: ShowPatch p => p x y -> DocSource

infopatch :: Patchy p => PatchInfo -> FL p x y -> Named p x ySource

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

thing :: ShowPatch p => p x y -> StringSource

things :: ShowPatch p => p x y -> StringSource

primIsAddfile :: PrimClassify prim => prim x y -> BoolSource

primIsHunk :: PrimClassify prim => prim x y -> BoolSource

primIsSetpref :: PrimClassify prim => prim x y -> BoolSource

merge :: Merge p => (p :\/: p) x y -> (p :/\: p) x ySource

commute :: Commute p => (p :> p) x y -> Maybe ((p :> p) x y)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

resolveConflicts :: Conflict p => p x y -> [[Sealed (FL (PrimOf p) y)]]Source

class Effect p whereSource

Patches whose concrete effect which can be expressed as a list of primitive patches.

A minimal definition would be either of effect or effectRL.

Methods

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

Instances

Effect p => Effect (RL p) 
Effect p => Effect (FL p) 
PrimPatch prim => Effect (Patch prim) 
Effect p => Effect (Named p) 
Effect p => Effect (PatchInfoAnd p) 
PrimPatch prim => Effect (RealPatch prim) 

primIsBinary :: PrimClassify prim => prim x y -> BoolSource

primIsAdddir :: PrimClassify prim => prim x y -> BoolSource

invert :: Invert p => p x y -> p y xSource

invertFL :: Invert p => FL p x y -> RL p y xSource

invertRL :: Invert p => RL p x y -> FL p y xSource

commuteFLorComplain :: Commute p => (p :> FL p) x y -> Either (Sealed2 p) ((FL p :> p) x y)Source

commuteRL :: Commute p => (RL p :> p) x y -> Maybe ((p :> RL p) x y)Source

canonize :: PrimCanonize prim => 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.

sortCoalesceFL :: PrimCanonize prim => 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.

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

patchcontents :: Named p x y -> FL p x ySource

apply :: (Apply p, ApplyMonad m (ApplyState p)) => p x y -> m ()Source

applyToTree :: (Apply p, Functor m, Monad m, ApplyState p ~ Tree) => p x y -> Tree m -> m (Tree m)Source

Apply a patch to a Tree, yielding a new Tree.

summary :: ShowPatch p => p x y -> DocSource

summaryFL :: ShowPatch p => FL p x y -> DocSource

plainSummaryPrims :: PrimDetails prim => FL prim x y -> DocSource

adddeps :: Named p x y -> [PatchInfo] -> Named p x ySource