- removeFL :: (MyEq p, Commute p) => p -> FL p -> Maybe (FL p)
- removeRL :: (MyEq p, Commute p) => p -> RL p -> Maybe (RL p)
- removeCommon :: (MyEq p, Commute p) => (FL p :\/: FL p) -> FL p :\/: FL p
- commuteWhatWeCanFL :: Commute p => (p :> FL p) -> FL p :> (p :> FL p)
- commuteWhatWeCanRL :: Commute p => (RL p :> p) -> RL p :> (p :> RL p)
- genCommuteWhatWeCanRL :: ((p :> p) -> Maybe (p :> p)) -> (RL p :> p) -> RL p :> (p :> RL p)
- partitionFL :: Commute p => (p -> Bool) -> FL p -> FL p :> (FL p :> FL p)
- partitionRL :: Commute p => (p -> Bool) -> RL p -> RL p :> RL p
- simpleHeadPermutationsFL :: Commute p => FL p -> [FL p]
- headPermutationsRL :: Commute p => RL p -> [RL p]
- headPermutationsFL :: Commute p => FL p -> [p :> FL p]
- removeSubsequenceFL :: (MyEq p, Commute p) => FL p -> FL p -> Maybe (FL p)
- removeSubsequenceRL :: (MyEq p, Commute p) => RL p -> RL p -> Maybe (RL p)
- partitionConflictingFL :: (Commute p1, Invert p1) => CommuteFn p1 p2 -> FL p1 -> p2 -> FL p1 :> FL p1
- type CommuteFn p1 p2 = (p1 :> p2) -> Maybe (p2 :> p1)
- selfCommuter :: Commute p => CommuteFn p p
- commuterIdRL :: CommuteFn p1 p2 -> CommuteFn p1 (RL p2)
Documentation
simpleHeadPermutationsFL :: Commute p => FL p -> [FL p]Source
This is a minor variant of headPermutationsFL
with each permutation
is simply returned as a FL
headPermutationsRL :: Commute p => RL p -> [RL p]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 -> [p :> FL p]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 :: (MyEq p, Commute p) => FL p -> FL p -> Maybe (FL p)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 :: (MyEq p, Commute p) => RL p -> RL p -> Maybe (RL p)Source
removeSubsequenceRL
is like removeSubsequenceFL
except that it works
on RL
partitionConflictingFL :: (Commute p1, Invert p1) => CommuteFn p1 p2 -> FL p1 -> p2 -> FL p1 :> FL p1Source
Partition a list into the patches that commute with the given patch and those that don't (including dependencies)
type CommuteFn p1 p2 = (p1 :> p2) -> Maybe (p2 :> p1)Source
CommuteFn is the basis of a general framework for building up commutation operations between different patch types in a generic manner. Unfortunately type classes are not well suited to the problem because of the multiple possible routes by which the commuter for (FL p1, FL p2) can be built out of the commuter for (p1, p2) - and more complicated problems when we start building multiple constructors on top of each other. The type class resolution machinery really can't cope with selecting some route, because it doesn't know that all possible routes should be equivalent.
selfCommuter :: Commute p => CommuteFn p pSource
Build a commuter between a patch and itself using the operation from the type class.
commuterIdRL :: CommuteFn p1 p2 -> CommuteFn p1 (RL p2)Source