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

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.Depends

Synopsis

Documentation

getUncovered :: PatchSet rt 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 :: Commute p => PatchSet rt p wStart wX -> PatchSet rt p wStart wY -> Bool Source #

findCommonAndUncommon :: forall rt p wStart wX wY. Commute p => PatchSet rt p wStart wX -> PatchSet rt p wStart wY -> Fork (PatchSet rt p) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wStart wX wY Source #

mergeThem :: Merge p => PatchSet rt p wStart wX -> PatchSet rt p wStart wY -> Sealed (FL (PatchInfoAnd rt p) wX) Source #

findCommonWithThem :: Commute p => PatchSet rt p wStart wX -> PatchSet rt p wStart wY -> (PatchSet rt p :> FL (PatchInfoAnd rt p)) wStart wX Source #

countUsThem :: Commute p => PatchSet rt p wStart wX -> PatchSet rt p wStart wY -> (Int, Int) Source #

removeFromPatchSet :: Commute p => FL (PatchInfoAnd rt p) wX wY -> PatchSet rt p wStart wY -> Maybe (PatchSet rt p wStart wX) Source #

slightlyOptimizePatchset :: PatchSet rt p wStart wX -> PatchSet rt 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 'clean :> unclean' state.

splitOnTag :: Commute p => PatchInfo -> PatchSet rt p wStart wX -> Maybe ((PatchSet rt p :> RL (PatchInfoAnd rt 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.

patchSetUnion :: Merge p => [SealedPatchSet rt p wStart] -> SealedPatchSet rt p wStart Source #

patchSetIntersection :: Commute p => [SealedPatchSet rt p wStart] -> SealedPatchSet rt p wStart Source #

findUncommon :: Commute p => PatchSet rt p wStart wX -> PatchSet rt p wStart wY -> (FL (PatchInfoAnd rt p) :\/: FL (PatchInfoAnd rt p)) wX wY Source #

merge2FL :: Merge p => FL (PatchInfoAnd rt p) wX wY -> FL (PatchInfoAnd rt p) wX wZ -> (FL (PatchInfoAnd rt p) :/\: FL (PatchInfoAnd rt 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 some 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 mergeFL?) (bf: I guess what was meant here is that merge2FL works in the the way it does because it considers patch meta data whereas mergeFL cannot since it must work for primitive patches, too.

getDeps :: RepoPatch p => FL (Named p) wA wR -> FL (PatchInfoAnd rt p) wX wY -> [SPatchAndDeps p] Source #

Searchs dependencies in repoFL of the patches in getDepsFL.

type SPatchAndDeps p = (Sealed2 (LabelledPatch (Named p)), Sealed2 (FL (LabelledPatch (Named p)))) Source #

S(ealed) Patch and his dependencies.