darcs-2.18.2: a distributed, interactive, smart revision control system
Safe HaskellSafe-Inferred
LanguageHaskell2010

Darcs.Patch

Synopsis

Documentation

class PrimPatch (PrimOf p) => PrimPatchBase p Source #

Associated Types

type PrimOf (p :: * -> * -> *) :: * -> * -> * Source #

Instances

Instances details
PrimPatchBase p => PrimPatchBase (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

Associated Types

type PrimOf (Invertible p) :: Type -> Type -> Type Source #

PrimPatchBase p => PrimPatchBase (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Associated Types

type PrimOf (Named p) :: Type -> Type -> Type Source #

PrimPatchBase p => PrimPatchBase (PatchInfoAndG p) Source # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

Associated Types

type PrimOf (PatchInfoAndG p) :: Type -> Type -> Type Source #

PrimPatch prim => PrimPatchBase (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Associated Types

type PrimOf (RebaseChange prim) :: Type -> Type -> Type Source #

PrimPatchBase p => PrimPatchBase (WithDroppedDeps p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Associated Types

type PrimOf (WithDroppedDeps p) :: Type -> Type -> Type Source #

PrimPatch prim => PrimPatchBase (RebaseFixup prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Fixup

Associated Types

type PrimOf (RebaseFixup prim) :: Type -> Type -> Type Source #

PrimPatch prim => PrimPatchBase (RepoPatchV1 prim) Source # 
Instance details

Defined in Darcs.Patch.V1.Core

Associated Types

type PrimOf (RepoPatchV1 prim) :: Type -> Type -> Type Source #

PrimPatch prim => PrimPatchBase (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Associated Types

type PrimOf (RepoPatchV2 prim) :: Type -> Type -> Type Source #

PrimPatchBase p => PrimPatchBase (FL p) Source # 
Instance details

Defined in Darcs.Patch.FromPrim

Associated Types

type PrimOf (FL p) :: Type -> Type -> Type Source #

PrimPatchBase p => PrimPatchBase (RL p) Source # 
Instance details

Defined in Darcs.Patch.FromPrim

Associated Types

type PrimOf (RL p) :: Type -> Type -> Type Source #

PrimPatch prim => PrimPatchBase (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Associated Types

type PrimOf (RepoPatchV3 name prim) :: Type -> Type -> Type Source #

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

Instances details
Apply p => Apply (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Associated Types

type ApplyState (Named p) :: (Type -> Type) -> Type Source #

Methods

apply :: ApplyMonad (ApplyState (Named p)) m => Named p wX wY -> m () Source #

unapply :: ApplyMonad (ApplyState (Named p)) m => Named p wX wY -> m () Source #

Commute p => Commute (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

commute :: (Named p :> Named p) wX wY -> Maybe ((Named p :> Named p) wX wY) Source #

(Commute p, Conflict p, Summary p, PrimPatchBase p, PatchListFormat p, ShowPatch p) => Conflict (Named p) Source #

This instance takes care of handling the interaction between conflict resolution and explicit dependencies. A conflict involves a set of two or more patches and the general rule is that the conflict is considered resolved if there is another (later) patch that (transitively) depends on each of the (mutually) conflicting patches.

This principle extends to explicit dependencies between Named patches. In particular, recording a tag has the effect of resolving any as yet unresolved conflicts in a repo.

In general a Named patch contains multiple changes ( a "changeset"). Consider the named patches

  Named A [] a
  Named B [] (b1;b2)
  Named C [] c
  Named D [A,B] _

where, at the RepoPatch level, a conflicts with b1, and c with b2. D depends explicitly on both A and B, so it fully covers the conflict between a and b1 and thus we would be justified to consider that particular conflict as resolved. Unfortunately we cannot detect this at the Named patch level because RepoPatchV1 and V2 have no notion of patch identities. Thus, at the Named level the two underlying conflicts appear as a single large conflict between the three named patches A, B, and C, and this means that patch D does not count as a (partial) resolution (even though it arguably should).

When we decide that a set of conflicting Named patches is resolved, we move the RepoPatches contained in them to the context of the resolution. For all other named patches, we must commute as much of their contents as possible past the ones marked as resolved, using commutation at the RepoPatch level (i.e. ignoring explicit dependencies).

Instance details

Defined in Darcs.Patch.Named

Methods

isConflicted :: Named p wX wY -> Bool Source #

resolveConflicts :: RL (Named p) wO wX -> RL (Named p) wX wY -> [ConflictDetails (PrimOf (Named p)) wY] Source #

(Commute p, Conflict p, Summary p, PrimPatchBase p, PatchListFormat p, ShowPatch p) => Conflict (PatchInfoAnd p) Source # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

PatchDebug p => PatchDebug (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

patchDebugDummy :: Named p wX wY -> () Source #

Effect p => Effect (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

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

IsHunk (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

isHunk :: Named p wX wY -> Maybe (FileHunk (ObjectIdOfPatch (Named p)) wX wY) Source #

PatchListFormat (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

PrimPatchBase p => PrimPatchBase (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Associated Types

type PrimOf (Named p) :: Type -> Type -> Type Source #

Ident (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

ident :: Named p wX wY -> PatchId (Named p) Source #

PatchInspect p => PatchInspect (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

listTouchedFiles :: Named p wX wY -> [AnchoredPath] Source #

hunkMatches :: (ByteString -> Bool) -> Named p wX wY -> Bool Source #

CleanMerge p => CleanMerge (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

cleanMerge :: (Named p :\/: Named p) wX wY -> Maybe ((Named p :/\: Named p) wX wY) Source #

Merge p => Merge (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

merge :: (Named p :\/: Named p) wX wY -> (Named p :/\: Named p) wX wY Source #

HasDeps (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

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

(ReadPatch p, PatchListFormat p) => ReadPatch (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

readPatch' :: Parser (Sealed (Named p wX)) Source #

Check p => Check (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

isInconsistent :: Named p wX wY -> Maybe Doc Source #

RepairToFL p => Repair (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

applyAndTryToFix :: ApplyMonad (ApplyState (Named p)) m => Named p wX wY -> m (Maybe (String, Named p wX wY)) Source #

RepairToFL p => Repair (PatchInfoAnd p) Source # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

(Apply p, IsHunk p, PatchListFormat p, ObjectId (ObjectIdOfPatch p), ShowContextPatch p) => ShowContextPatch (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

(Summary p, PatchListFormat p, PrimPatchBase p, ShowPatch p) => ShowPatch (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

content :: Named p wX wY -> Doc Source #

description :: Named p wX wY -> Doc Source #

summary :: Named p wX wY -> Doc Source #

summaryFL :: FL (Named p) wX wY -> Doc Source #

thing :: Named p wX wY -> String Source #

things :: Named p wX wY -> String Source #

(PatchListFormat p, ShowPatchBasic p) => ShowPatchBasic (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

showPatch :: ShowPatchFor -> Named p wX wY -> Doc Source #

Summary p => Summary (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

(PrimPatchBase p, Unwind p) => Unwind (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

fullUnwind :: Named p wX wY -> Unwound (PrimOf (Named p)) wX wY Source #

(Commute p, Eq2 p) => Eq2 (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

unsafeCompare :: Named p wA wB -> Named p wC wD -> Bool Source #

(=\/=) :: Named p wA wB -> Named p wA wC -> EqCheck wB wC Source #

(=/\=) :: Named p wA wC -> Named p wB wC -> EqCheck wA wB Source #

Show2 p => Show2 (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

showDict2 :: ShowDict (Named p wX wY) Source #

Show2 p => Show2 (PatchInfoAnd p) Source # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

Methods

showDict2 :: ShowDict (PatchInfoAnd p wX wY) Source #

Show2 p => Show1 (Named p wX) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

showDict1 :: Dict (Show (Named p wX wX0)) Source #

Show2 p => Show1 (PatchInfoAnd p wX) Source # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

Methods

showDict1 :: Dict (Show (PatchInfoAnd p wX wX0)) Source #

Show2 p => Show (Named p wX wY) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

showsPrec :: Int -> Named p wX wY -> ShowS #

show :: Named p wX wY -> String #

showList :: [Named p wX wY] -> ShowS #

type ApplyState (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

type PrimOf (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

type PrimOf (Named p) = PrimOf p
type PatchId (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

type family ApplyState p :: (* -> *) -> * Source #

Instances

Instances details
type ApplyState Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.FileUUID.Apply

type ApplyState Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Apply

type ApplyState Prim Source # 
Instance details

Defined in Darcs.Patch.V1.Prim

type ApplyState Prim Source # 
Instance details

Defined in Darcs.Patch.V2.Prim

type ApplyState (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

type ApplyState (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

type ApplyState (PatchInfoAndG p) Source # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

type ApplyState (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

type ApplyState (RebaseFixup prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Fixup

type ApplyState (RebaseFixup prim) = ApplyState prim
type ApplyState (RepoPatchV1 prim) Source # 
Instance details

Defined in Darcs.Patch.V1.Apply

type ApplyState (RepoPatchV1 prim) = ApplyState prim
type ApplyState (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

type ApplyState (RepoPatchV2 prim) = ApplyState prim
type ApplyState (FL p) Source # 
Instance details

Defined in Darcs.Patch.Apply

type ApplyState (FL p) = ApplyState p
type ApplyState (RL p) Source # 
Instance details

Defined in Darcs.Patch.Apply

type ApplyState (RL p) = ApplyState p
type ApplyState (PrimWithName name p) Source # 
Instance details

Defined in Darcs.Patch.Prim.WithName

type ApplyState (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

type ApplyState (RepoPatchV3 name prim) = ApplyState prim
type ApplyState (PatchSeq p) Source # 
Instance details

Defined in Darcs.UI.Commands.Test.Impl

rmfile :: PrimConstruct prim => AnchoredPath -> prim wX wY Source #

addfile :: PrimConstruct prim => AnchoredPath -> prim wX wY Source #

rmdir :: PrimConstruct prim => AnchoredPath -> prim wX wY Source #

adddir :: PrimConstruct prim => AnchoredPath -> prim wX wY Source #

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

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

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

anonymous :: FromPrim p => FL (PrimOf p) wX wY -> IO (Named p wX wY) Source #

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

showPatchWithContext :: (ApplyMonadTrans (ApplyState p) m, ShowContextPatch p) => ShowPatchFor -> ApplyState p m -> p wX wY -> m Doc Source #

Like showPatchWithContextAndApply but without applying the patch in the monad m.

content :: ShowPatch p => p wX wY -> Doc Source #

infopatch :: forall p wX wY. FromPrim p => PatchInfo -> FL (PrimOf 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 #

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 tokChars old new input replaces all occurrences of the old token with the new one, throughout the input.

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

for PatchTest

resolveConflicts :: Conflict p => RL p wO wX -> RL p wX wY -> [ConflictDetails (PrimOf p) wY] Source #

The first parameter is a context containing all patches preceding the ones for which we want to calculate the conflict resolution, which is the second parameter. Each element of the result list represents the resolution of one maximal set of transitively conflicting alternatives, in other words, a connected subset of the conflict graph. But the elements themselves must not conflict with each other, guaranteeing that they can be cleanly merged into a single FL of prims.

class Effect p Source #

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

A minimal definition would be either of effect or effectRL.

Minimal complete definition

effect

Instances

Instances details
Effect p => Effect (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

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

Effect p => Effect (PatchInfoAndG p) Source # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

Methods

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

Effect p => Effect (WithDroppedDeps p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Methods

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

PrimPatch prim => Effect (RepoPatchV1 prim) Source # 
Instance details

Defined in Darcs.Patch.V1.Commute

Methods

effect :: RepoPatchV1 prim wX wY -> FL (PrimOf (RepoPatchV1 prim)) wX wY Source #

PrimPatch prim => Effect (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

effect :: RepoPatchV2 prim wX wY -> FL (PrimOf (RepoPatchV2 prim)) wX wY Source #

Effect p => Effect (FL p) Source # 
Instance details

Defined in Darcs.Patch.Effect

Methods

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

Effect p => Effect (RL p) Source # 
Instance details

Defined in Darcs.Patch.Effect

Methods

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

Effect (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

effect :: RepoPatchV3 name prim wX wY -> FL (PrimOf (RepoPatchV3 name prim)) wX wY Source #

effect :: Effect p => p wX wY -> FL (PrimOf p) wX wY 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 #

commuteFL :: Commute p => (p :> FL p) wX wY -> Maybe ((FL p :> p) wX wY) Source #

commuteFL commutes a single element past a FL.

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

commuteRL commutes a RL past a single element.

canonizeFL :: (IsHunk prim, PrimCoalesce prim, PrimConstruct prim) => DiffAlgorithm -> FL prim wX wY -> FL prim wX wY Source #

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

XXX Why not? How does it differ? The implementation for Prim.V1 does sortCoalesceFL and then invokes the diff algorithm for each hunk. How can that be any different to applying the sequence and then taking the diff? Is this merely because diff does not sort by file path?

Besides, diff and apply must be inverses in the sense that for any two states {start, end}, we have

diff start (apply (diff start end)) == end

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

This is similar to tryToShrink but always gives back a result: if the sequence could not be shrunk we merely give back a sorted version.

This method is included in the class for optimization. Instances are free to use defaultSortCoalesceFL.

tryToShrink :: PrimCoalesce prim => FL prim wX wY -> Maybe (FL prim wX wY) Source #

Try to shrink the input sequence by getting rid of self-cancellations and identity patches or by coalescing patches. Also sort patches according to some internally defined order (specific to the patch type) as far as possible while respecting dependencies. A result of Nothing means that we could not shrink the input.

This method is included in the class for optimization. Instances are free to use defaultTryToShrink.

patchname :: Named p wX wY -> String Source #

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

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

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

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

maybeApplyToTree :: (Apply p, ApplyState p ~ Tree, MonadCatch m) => p wX wY -> Tree m -> m (Maybe (Tree m)) Source #

Attempts to apply a given patch to a Tree. If the apply fails, we return Nothing, otherwise we return the updated Tree.

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

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

plainSummary :: (Summary e, PrimDetails (PrimOf e)) => e wX wY -> Doc Source #

xmlSummary :: (Summary p, PrimDetails (PrimOf p)) => p wX wY -> Doc Source #

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

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

getdeps :: HasDeps p => p wX wY -> [PatchInfo] Source #

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

hopefully :: PatchInfoAndG p wA wB -> p wA wB Source #

hopefully hp tries to get a patch from a PatchInfoAnd value. If it fails, it outputs an error "failed to read patch: <description of the patch>". We get the description of the patch from the info part of hp