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

Darcs.Patch.Conflict

Synopsis

Documentation

class Conflict p where Source #

Methods

isConflicted :: p wX wY -> Bool Source #

resolveConflicts :: 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.

Instances

Instances details
(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

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

Defined in Darcs.Patch.V1.Commute

Methods

isConflicted :: RepoPatchV1 prim wX wY -> Bool Source #

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

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

Defined in Darcs.Patch.V2.RepoPatch

Methods

isConflicted :: RepoPatchV2 prim wX wY -> Bool Source #

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

(SignedId name, StorableId name, PrimPatch prim) => Conflict (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Resolution

Methods

isConflicted :: RepoPatchV3 name prim wX wY -> Bool Source #

resolveConflicts :: RL (RepoPatchV3 name prim) wO wX -> RL (RepoPatchV3 name prim) wX wY -> [ConflictDetails (PrimOf (RepoPatchV3 name prim)) wY] Source #

data ConflictDetails prim wX Source #

Constructors

ConflictDetails 

Fields

type Mangled prim wX = Sealed (FL prim wX) Source #

Result of mangling a single Unravelled.

type Unravelled prim wX = [Sealed (FL prim wX)] Source #

A list of conflicting alternatives. They form a connected component of the conflict graph i.e. one transitive conflict.

mangleOrFail :: PrimMangleUnravelled prim => Unravelled prim wX -> ConflictDetails prim wX Source #

For one conflict (a connected set of conflicting prims), store the conflicting parts and, if possible, their mangled version.

combineConflicts :: forall p wX wY. CommuteNoConflicts p => (forall wA wB. p wA wB -> [Unravelled (PrimOf p) wB]) -> RL p wX wY -> [Unravelled (PrimOf p) wY] Source #

By definition, a conflicting patch is resolved if another patch (that is not itself conflicted) depends on the conflict. If the representation of conflicts is self-contained as it is for V1 and V2, then we can calculate the maximal set of conflicting alternatives for a conflict separately for each conflictor at the end of a repo. This function can then be used to lift this to an RL of patches.

So, when looking for conflicts in a list of patches, we go through the whole list looking for individual patches that represent a conflict. But then we try to commute them past all the patches we've already seen. If we fail, i.e. there's something that depends on the conflict, then we forget about the conflict; this is the Nothing case of the commuteNoConflictsFL call. Otherwise the patch is now in the correct position to extract the conflicting alternatives.

findConflicting :: forall p wX wY wZ. (Commute p, Conflict p, ShowPatch p) => RL p wX wY -> p wY wZ -> (RL p :> (p :> RL p)) wX wZ Source #

Find all patches in the context that conflict with a given patch, commuting them to the head (past the patch in question).

This actually works by commuting the patch and its dependencies backward until it becomes unconflicted, then minimizing the trailing patches by re-commuting them backward as long as that keeps the patch unconflicted.

Precondition: the context must contain all conflicting patches.