| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Darcs.Patch.Permutations
Contents
Synopsis
- removeFL :: (Eq2 p, Commute p) => p wX wY -> FL p wX wZ -> Maybe (FL p wY wZ)
- removeRL :: (Eq2 p, Commute p) => p wY wZ -> RL p wX wZ -> Maybe (RL p wX wY)
- removeCommon :: (Eq2 p, Commute p) => (FL p :\/: FL p) wX wY -> (FL p :\/: FL p) wX wY
- commuteWhatWeCanFL :: Commute p => (p :> FL p) wX wY -> (FL p :> (p :> FL p)) wX wY
- commuteWhatWeCanRL :: Commute p => (RL p :> p) wX wY -> (RL p :> (p :> RL p)) wX wY
- genCommuteWhatWeCanRL :: Commute p => (forall wA wB. (p :> q) wA wB -> Maybe ((q :> p) wA wB)) -> (RL p :> q) wX wY -> (RL p :> (q :> RL p)) wX wY
- genCommuteWhatWeCanFL :: Commute q => (forall wA wB. (p :> q) wA wB -> Maybe ((q :> p) wA wB)) -> (p :> FL q) wX wY -> (FL q :> (p :> FL q)) wX wY
- partitionFL :: Commute p => (forall wU wV. p wU wV -> Bool) -> FL p wX wY -> (FL p :> (FL p :> FL p)) wX wY
- partitionRL :: forall p wX wY. Commute p => (forall wU wV. p wU wV -> Bool) -> RL p wX wY -> (RL p :> RL p) wX wY
- partitionFL' :: Commute p => (forall wU wV. p wU wV -> Bool) -> RL p wA wB -> RL p wB wC -> FL p wC wD -> (FL p :> (RL p :> RL p)) wA wD
- simpleHeadPermutationsFL :: Commute p => FL p wX wY -> [FL p wX wY]
- headPermutationsRL :: Commute p => RL p wX wY -> [RL p wX wY]
- headPermutationsFL :: Commute p => FL p wX wY -> [(p :> FL p) wX wY]
- permutationsRL :: Commute p => RL p wX wY -> [RL p wX wY]
- removeSubsequenceFL :: (Eq2 p, Commute p) => FL p wA wB -> FL p wA wC -> Maybe (FL p wB wC)
- removeSubsequenceRL :: (Eq2 p, Commute p) => RL p wAb wAbc -> RL p wA wAbc -> Maybe (RL p wA wAb)
- partitionConflictingFL :: (Commute p, CleanMerge p) => FL p wX wY -> FL p wX wZ -> (FL p :> FL p) wX wY
Documentation
genCommuteWhatWeCanRL :: Commute p => (forall wA wB. (p :> q) wA wB -> Maybe ((q :> p) wA wB)) -> (RL p :> q) wX wY -> (RL p :> (q :> RL p)) wX wY Source #
genCommuteWhatWeCanFL :: Commute q => (forall wA wB. (p :> q) wA wB -> Maybe ((q :> p) wA wB)) -> (p :> FL q) wX wY -> (FL q :> (p :> FL q)) wX wY Source #
Arguments
| :: Commute p | |
| => (forall wU wV. p wU wV -> Bool) | predicate; if true we would like the patch in the "left" list | 
| -> FL p wX wY | input  | 
| -> (FL p :> (FL p :> FL p)) wX wY | "left", "middle" and "right" | 
Split an FL according to a predicate, using commutation as necessary,
 into those that satisfy the predicate and can be commuted to the left, and
 those that do not satisfy it and can be commuted to the right. Whatever
 remains stays in the middle.
Note that the predicate p should be invariant under commutation:
 if commute(x:>y)==Just(y':>x') then p x == p x' && p y == p y'.
Arguments
| :: Commute p | |
| => (forall wU wV. p wU wV -> Bool) | predicate; if true we would like the patch in the "right" list | 
| -> RL p wX wY | input  | 
| -> (RL p :> RL p) wX wY | "left" and "right" results | 
Split an RL according to a predicate, using commutation as necessary,
 into those that satisfy the predicate and can be commuted to the right, and
 those that don't, i.e. either do not satisfy the predicate or cannot be
 commuted to the right.
Note that the predicate p should be invariant under commutation:
 if commute(x:>y)==Just(y':>x') then p x == p x' && p y == p y'.
partitionFL' :: Commute p => (forall wU wV. p wU wV -> Bool) -> RL p wA wB -> RL p wB wC -> FL p wC wD -> (FL p :> (RL p :> RL p)) wA wD Source #
simpleHeadPermutationsFL :: Commute p => FL p wX wY -> [FL p wX wY] Source #
This is a minor variant of headPermutationsFL with each permutation
   is simply returned as a FL
headPermutationsRL :: Commute p => RL p wX wY -> [RL p wX wY] Source #
headPermutationsRL is like headPermutationsFL, except that we
   operate on an RL (in other words, we are pushing things to the end of a
   patch sequence instead of to the beginning).
headPermutationsFL :: Commute p => FL p wX wY -> [(p :> FL p) wX wY] Source #
headPermutationsFL p:>:ps returns all the permutations of the list
   in which one element of ps is commuted past p
Suppose we have a sequence of patches
X h a y s-t-c k
Suppose furthermore that the patch c depends on t, which in turn
   depends on s.  This function will return
X :> h a y s t c k h :> X a y s t c k a :> X h y s t c k y :> X h a s t c k s :> X h a y t c k k :> X h a y s t c
removeSubsequenceFL :: (Eq2 p, Commute p) => FL p wA wB -> FL p wA wC -> Maybe (FL p wB wC) Source #
removeSubsequenceFL ab abc returns Just c' where all the patches in
   ab have been commuted out of it, if possible.  If this is not possible
   for any reason (the set of patches ab is not actually a subset of abc,
   or they can't be commuted out) we return Nothing.
removeSubsequenceRL :: (Eq2 p, Commute p) => RL p wAb wAbc -> RL p wA wAbc -> Maybe (RL p wA wAb) Source #
removeSubsequenceRL is like removeSubsequenceFL except that it works
   on RL
partitionConflictingFL :: (Commute p, CleanMerge p) => FL p wX wY -> FL p wX wZ -> (FL p :> FL p) wX wY Source #
Partition a list into the patches that merge cleanly with the given patch and those that don't (including dependencies)