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

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.Depends

Synopsis

Documentation

getUncovered :: PatchSet p wStart wX -> [PatchInfo] Source

getUncovered ps returns the PatchInfo for all the patches in ps that are not depended on by anything else *through explicit dependencies*. Tags are a likely candidate, although we may also find some non-tag patches in this list.

Keep in mind that in a typical repository with a lot of tags, only a small fraction of tags would be returned as they would be at least indirectly depended on by the topmost ones.

areUnrelatedRepos :: (Patchy p, NameHack p) => PatchSet p wStart wX -> PatchSet p wStart wY -> Bool Source

findCommonAndUncommon :: forall p wStart wX wY. (Patchy p, NameHack p) => PatchSet p wStart wX -> PatchSet p wStart wY -> Fork (PatchSet p) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) wStart wX wY Source

mergeThem :: (Patchy p, Merge p, NameHack p) => PatchSet p wStart wX -> PatchSet p wStart wY -> Sealed (FL (PatchInfoAnd p) wX) Source

findCommonWithThem :: (Patchy p, NameHack p) => PatchSet p wStart wX -> PatchSet p wStart wY -> (PatchSet p :> FL (PatchInfoAnd p)) wStart wX Source

countUsThem :: (Patchy p, NameHack p) => PatchSet p wStart wX -> PatchSet p wStart wY -> (Int, Int) Source

removeFromPatchSet :: (Patchy p, NameHack p) => FL (PatchInfoAnd p) wX wY -> PatchSet p wStart wY -> Maybe (PatchSet p wStart wX) Source

slightlyOptimizePatchset :: PatchSet p wStart wX -> PatchSet p wStart wX Source

slightlyOptimizePatchset only works on the surface inventory (see optimizePatchset) and only optimises at most one tag in there, going for the most recent tag which has no non-depended patch after it. Older tags won't be clean, which means the PatchSet will not be in 'unclean :< clean' state.

splitOnTag :: (Patchy p, NameHack p) => PatchInfo -> PatchSet p wStart wX -> Maybe ((PatchSet p :> RL (PatchInfoAnd p)) wStart wX) Source

splitOnTag takes a tag's PatchInfo, and a PatchSet, and attempts to find the tag in the PatchSet, returning a pair: the clean PatchSet "up to" the tag, and a RL of patches after the tag; If the tag is not in the PatchSet, we return Nothing.

newsetUnion :: (Patchy p, Merge p, NameHack p) => [SealedPatchSet p wStart] -> SealedPatchSet p wStart Source

commuteToEnd :: forall p wStart wX wY. (Patchy p, NameHack p) => RL (PatchInfoAnd p) wX wY -> PatchSet p wStart wY -> (PatchSet p :> RL (PatchInfoAnd p)) wStart wX Source

findUncommon :: (Patchy p, NameHack p) => PatchSet p wStart wX -> PatchSet p wStart wY -> (FL (PatchInfoAnd p) :\/: FL (PatchInfoAnd p)) wX wY Source

merge2FL :: (Patchy p, Merge p, NameHack p) => FL (PatchInfoAnd p) wX wY -> FL (PatchInfoAnd p) wX wZ -> (FL (PatchInfoAnd p) :/\: FL (PatchInfoAnd p)) wY wZ Source

Merge two FLs (say L and R), starting in a common context. The result is a FL starting in the original end context of L, going to a new context that is the result of applying all patches from R on top of patches from L.

While this function is similar to mergeFL, there are three important differences to keep in mind:

  • mergeFL does not correctly deal with duplicate patches whereas this one does (Question from Eric Kow: in what sense? Why not fix the mergeFL instance?)
  • The conventional order we use in this function is reversed from mergeFL (so mergeFL r l vs. merge2FL l r. This does not matter so much for the former since you get both paths. (Question from Eric Kow: should we flip merge2FL for more uniformity in the code?)