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

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch

Contents

Synopsis

Documentation

data Named p wX wY 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).

Instances

class (Apply p, Commute 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) 
(Patchy p, NameHack p, (~) ((* -> *) -> *) (ApplyState p) Tree) => Patchy (Named p) 
Apply p => Patchy (RebaseName p) 
PrimPatch prim => Patchy (Patch prim) 
PrimPatch prim => Patchy (RealPatch prim) 
(Patchy p, NameHack p, (~) ((* -> *) -> *) (ApplyState p) Tree) => Patchy (PatchInfoAnd p) 
(PrimPatchBase p, PatchListFormat p, Patchy p, FromPrim p, Conflict p, Effect p, CommuteNoConflicts p, IsHunk p) => Patchy (Rebasing p) 
(PrimPatchBase p, Apply p, (~) ((* -> *) -> *) (ApplyState p) (ApplyState (PrimOf p)), Invert p) => Patchy (RebaseChange p) 
(PrimPatchBase p, PatchListFormat p, Conflict p, FromPrim p, Effect p, CommuteNoConflicts p, IsHunk p, Patchy p, (~) ((* -> *) -> *) (ApplyState p) (ApplyState (PrimOf p)), NameHack p) => Patchy (RebaseSelect p) 

fromPrim :: FromPrim p => PrimOf p wX wY -> p wX wY Source

fromPrims :: FromPrims p => FL (PrimOf p) wX wY -> p wX wY Source

rmfile :: PrimConstruct prim => FilePath -> prim wX wY Source

addfile :: PrimConstruct prim => FilePath -> prim wX wY Source

rmdir :: PrimConstruct prim => FilePath -> prim wX wY Source

adddir :: PrimConstruct prim => FilePath -> prim wX wY Source

move :: PrimConstruct prim => FilePath -> FilePath -> prim wX wY Source

hunk :: PrimConstruct prim => FilePath -> Int -> [ByteString] -> [ByteString] -> prim wX wY Source

tokreplace :: PrimConstruct prim => FilePath -> String -> String -> String -> prim wX wY Source

namepatch :: String -> String -> String -> [String] -> FL p wX wY -> IO (Named p wX wY) Source

anonymous :: FL p wX wY -> IO (Named p wX wY) Source

binary :: PrimConstruct prim => FilePath -> ByteString -> ByteString -> prim wX wY Source

description :: ShowPatch p => p wX wY -> Doc Source

showContextPatch :: (ShowPatch p, Monad m, ApplyMonadTrans m (ApplyState p), ApplyMonad m (ApplyState p)) => p wX wY -> m Doc Source

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.

showPatch :: ShowPatchBasic p => p wX wY -> Doc Source

showNicely :: ShowPatch p => p wX wY -> Doc Source

infopatch :: PatchInfo -> FL p wX wY -> Named p wX wY Source

changepref :: PrimConstruct prim => String -> String -> String -> prim wX wY Source

thing :: ShowPatch p => p wX wY -> String Source

things :: ShowPatch p => p wX wY -> String Source

primIsAddfile :: PrimClassify prim => prim wX wY -> Bool Source

primIsHunk :: PrimClassify prim => prim wX wY -> Bool Source

primIsSetpref :: PrimClassify prim => prim wX wY -> Bool Source

merge :: Merge p => (p :\/: p) wX wY -> (p :/\: p) wX wY Source

commute :: Commute p => (p :> p) wX wY -> Maybe ((p :> p) wX wY) Source

hunkMatches :: PatchInspect p => (ByteString -> Bool) -> p wX wY -> Bool Source

forceTokReplace :: String -> ByteString -> ByteString -> ByteString -> ByteString Source

forceTokReplace replaces all occurrences of the old token with the new token, throughout the input ByteString.

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

for PatchTest

resolveConflicts :: Conflict p => p wX wY -> [[Sealed (FL (PrimOf p) wY)]] Source

class Effect p where Source

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

A minimal definition would be either of effect or effectRL.

Minimal complete definition

Nothing

Methods

effect :: p wX wY -> FL (PrimOf p) wX wY Source

primIsBinary :: PrimClassify prim => prim wX wY -> Bool Source

primIsAdddir :: PrimClassify prim => prim wX wY -> Bool Source

invert :: Invert p => p wX wY -> p wY wX Source

invertFL :: Invert p => FL p wX wY -> RL p wY wX Source

invertRL :: Invert p => RL p wX wY -> FL p wY wX Source

commuteFLorComplain :: Commute p => (p :> FL p) wX wY -> Either (Sealed2 p) ((FL p :> p) wX wY) Source

commuteFLorComplain attempts to commute a single element past a FL. If any individual commute fails, then we return the patch that first patch that cannot be commuted past.

commuteRL :: Commute p => (RL p :> p) wX wY -> Maybe ((p :> RL p) wX wY) Source

commuteRL commutes a RL past a single element.

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

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

tryToShrink :: PrimCanonize prim => 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?

patchcontents :: Named p wX wY -> FL p wX wY Source

apply :: (Apply p, ApplyMonad m (ApplyState p)) => p wX wY -> m () Source

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

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

effectOnFilePaths :: (Apply p, ApplyState p ~ Tree) => p wX wY -> [FilePath] -> [FilePath] Source

summary :: ShowPatch p => p wX wY -> Doc Source

summaryFL :: ShowPatch p => FL p wX wY -> Doc Source

plainSummary :: (Conflict e, Effect e, PrimPatchBase e) => e wX wY -> Doc Source

xmlSummary :: (Effect p, Conflict p, PrimPatchBase p) => p wX wY -> Doc Source

plainSummaryPrims :: PrimDetails prim => FL prim wX wY -> Doc Source

adddeps :: Named p wX wY -> [PatchInfo] -> Named p wX wY Source

getdeps :: Named p wX wY -> [PatchInfo] Source

isInconsistent :: Check p => p wX wY -> Maybe Doc Source