Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Conflict p where
- resolveConflicts :: RL p wO wX -> RL p wX wY -> [ConflictDetails (PrimOf p) wY]
- data ConflictDetails prim wX = ConflictDetails {
- conflictMangled :: Maybe (Mangled prim wX)
- conflictParts :: Unravelled prim wX
- type Mangled prim wX = Sealed (FL prim wX)
- type Unravelled prim wX = [Sealed (FL prim wX)]
- mangleOrFail :: PrimMangleUnravelled prim => Unravelled prim wX -> ConflictDetails prim wX
- 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]
Documentation
class Conflict p where 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
PrimPatch prim => Conflict (RepoPatchV1 prim) Source # | |
Defined in Darcs.Patch.V1.Commute resolveConflicts :: RL (RepoPatchV1 prim) wO wX -> RL (RepoPatchV1 prim) wX wY -> [ConflictDetails (PrimOf (RepoPatchV1 prim)) wY] Source # | |
PrimPatch prim => Conflict (RepoPatchV2 prim) Source # | |
Defined in Darcs.Patch.V2.RepoPatch resolveConflicts :: RL (RepoPatchV2 prim) wO wX -> RL (RepoPatchV2 prim) wX wY -> [ConflictDetails (PrimOf (RepoPatchV2 prim)) wY] Source # | |
(Commute p, Conflict p) => Conflict (Named p) Source # | This instance takes care of handling the interaction between conflict
resolution and explicit dependencies. By definition, a conflict counts as
resolved if another patch depends on it. This principle extends to explicit
dependencies between This means we count any patch inside a |
Defined in Darcs.Patch.Named resolveConflicts :: RL (Named p) wO wX -> RL (Named p) wX wY -> [ConflictDetails (PrimOf (Named p)) wY] Source # | |
(Commute p, Conflict p) => Conflict (PatchInfoAnd rt p) Source # | |
Defined in Darcs.Patch.PatchInfoAnd resolveConflicts :: RL (PatchInfoAnd rt p) wO wX -> RL (PatchInfoAnd rt p) wX wY -> [ConflictDetails (PrimOf (PatchInfoAnd rt p)) wY] Source # | |
(SignedId name, StorableId name, PrimPatch prim) => Conflict (RepoPatchV3 name prim) Source # | |
Defined in Darcs.Patch.V3.Resolution 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 #
ConflictDetails | |
|
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 #
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.