Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Definitions used in this module:
- Explicit dependencies
- The set of patches that a (named) patch depends on "by name", i.e. irrespective of (non-)commutation (non commuting patches are implicit dependencies). The most important example are tags, but non-tag patches can also have explicit dependencies by recording them with --ask-deps.
- Covered
- A patch
p
is covered by a tagt
ift
explicitly depends onp
or a tag covered byt
explicitly depends onp
. In other words, the transitive closure of the relation "is depended on", restricted to situations where the right hand side is a tag. Note that it does not take explicit dependencies of non-tag patches into account at all. - Clean
- A tag
t
in a repository is clean if all patches prior to the tag are covered byt
. Tags normally start out as clean tags (the exception is if --ask-deps is used). It typically becomes unclean when it is merged into another repo (here the exceptions are if --reorder-patches is used, or if the target repo is actually a subset of the source repo).
Synopsis
- getUncovered :: PatchSet p wStart wX -> [PatchInfo]
- areUnrelatedRepos :: Commute p => PatchSet p Origin wX -> PatchSet p Origin wY -> Bool
- findCommon :: Commute p => PatchSet p Origin wX -> PatchSet p Origin wY -> Fork (PatchSet p) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wX wY
- findCommonWithThem :: Commute p => PatchSet p Origin wX -> PatchSet p Origin wY -> (PatchSet p :> FL (PatchInfoAnd p)) Origin wX
- findUncommon :: Commute p => PatchSet p Origin wX -> PatchSet p Origin wY -> (FL (PatchInfoAnd p) :\/: FL (PatchInfoAnd p)) wX wY
- patchSetMerge :: (Commute p, Merge p) => PatchSet p Origin wX -> PatchSet p Origin wY -> (FL (PatchInfoAnd p) :/\: FL (PatchInfoAnd p)) wX wY
- countUsThem :: Commute p => PatchSet p Origin wX -> PatchSet p Origin wY -> (Int, Int)
- removeFromPatchSet :: (Commute p, Eq2 p) => FL (PatchInfoAnd p) wX wY -> PatchSet p wStart wY -> Maybe (PatchSet p wStart wX)
- slightlyOptimizePatchset :: PatchSet p wStart wX -> PatchSet p wStart wX
- fullyOptimizePatchSet :: forall p wZ. Commute p => PatchSet p Origin wZ -> PatchSet p Origin wZ
- splitOnTag :: Commute p => PatchInfo -> PatchSet p wStart wX -> Maybe (PatchSet p wStart wX)
- patchSetUnion :: (Commute p, Merge p) => [SealedPatchSet p Origin] -> SealedPatchSet p Origin
- patchSetIntersection :: Commute p => [SealedPatchSet p Origin] -> SealedPatchSet p Origin
- cleanLatestTag :: Commute p => PatchSet p wStart wX -> PatchSet p wStart wX
- contextPatches :: PatchSet p wX wY -> (PatchSet p :> RL (PatchInfoAnd p)) wX wY
Documentation
getUncovered :: PatchSet p wStart wX -> [PatchInfo] Source #
Return the PatchInfo
for all the patches in a PatchSet
that are not
*explicitly* depended on by any tag (in the given PatchSet
).
This is exactly the set of patches that a new tag recorded on top
of the PatchSet
would explicitly depend on.
Note that the result is not minimal with respect to dependencies, not even explicit dependencies: explicit dependencies of regular (non-tag) patches are completely ignored.
findCommon :: Commute p => PatchSet p Origin wX -> PatchSet p Origin wY -> Fork (PatchSet p) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wX wY Source #
The symmetric difference between two PatchSet
s, expressed as a Fork
consisting of the intersection PatchSet
and the trailing lists of
left-only and right-only patches.
From a purely functional point of view this is a symmetric function.
However, laziness effects make it asymmetric: the LHS is more likely to be
evaluated fully, while the RHS is evaluated as sparingly as possible. For
efficiency, the LHS should come from the local repo and the RHS from the
remote one. This asymmetry can also have a semantic effect, namely if
PatchSet
s have *unavailable* patches or inventories, for instance when we
deal with a lazy clone of a repo that is no longer accessible. In this case
the order of arguments may determine whether the command fails or succeeds.
findCommonWithThem :: Commute p => PatchSet p Origin wX -> PatchSet p Origin wY -> (PatchSet p :> FL (PatchInfoAnd p)) Origin wX Source #
findUncommon :: Commute p => PatchSet p Origin wX -> PatchSet p Origin wY -> (FL (PatchInfoAnd p) :\/: FL (PatchInfoAnd p)) wX wY Source #
patchSetMerge :: (Commute p, Merge p) => PatchSet p Origin wX -> PatchSet p Origin wY -> (FL (PatchInfoAnd p) :/\: FL (PatchInfoAnd p)) wX wY Source #
removeFromPatchSet :: (Commute p, Eq2 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 #
fullyOptimizePatchSet :: forall p wZ. Commute p => PatchSet p Origin wZ -> PatchSet p Origin wZ Source #
Create a Tagged
section for every clean tag. For unclean tags we try to
make them clean, but only if that doesn't make an earlier clean tag dirty.
This means that the operation is idempotent and in particular monotonic,
which justifies the "optimize" in the name.
splitOnTag :: Commute p => PatchInfo -> PatchSet p wStart wX -> Maybe (PatchSet p wStart wX) Source #
Take a tag's PatchInfo
, and a PatchSet
, and attempt to find the tag in
the PatchSet
. If found, return a new PatchSet
, in which the tag is now
clean (and the last of the Tagged
list), while all patches that are not
covered by the tag are in the trailing list of patches.
If the tag is not in the PatchSet
, we return Nothing
.
patchSetUnion :: (Commute p, Merge p) => [SealedPatchSet p Origin] -> SealedPatchSet p Origin Source #
patchSetIntersection :: Commute p => [SealedPatchSet p Origin] -> SealedPatchSet p Origin Source #
cleanLatestTag :: Commute p => PatchSet p wStart wX -> PatchSet p wStart wX Source #
Reorder a PatchSet
such that the latest tag becomes clean.
contextPatches :: PatchSet p wX wY -> (PatchSet p :> RL (PatchInfoAnd p)) wX wY Source #
Split a PatchSet
at the latest clean tag. The left part is what comes
before the tag, the right part is the tag and its non-dependencies.