| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Darcs.Patch.Choices
Description
PatchChoices divides a sequence of patches into three sets: "first", "middle" and "last", such that all patches can be applied, if you first apply the first ones then the middle ones and then the last ones. Obviously if there are dependencies between the patches that will put a constraint on how you can choose to divide them up. The PatchChoices data type and associated functions are here to deal with many of the common cases that come up when choosing a subset of a group of patches.
forceLast tells PatchChoices that a particular patch is required to be in
 the "last" group, which also means that any patches that depend on it
 must be in the "last" group.
Internally, a PatchChoices doesn't always reorder the patches until
 it is asked for the final output (e.g. by get_first_choice).
 Instead, each patch is placed in a state of definitely first,
 definitely last and undecided; undecided leans towards
 "middle". The patches that are first are commuted to the head
 immediately, but patches that are middle and last are mixed
 together. In case you're wondering about the first-middle-last
 language, it's because in some cases the "yes" answers will be last
 (as is the case for the revert command), and in others first (as in
 record, pull and push).
Some patch marked "middle" may in fact be unselectable because of dependencies: when a patch is marked "last", its dependencies are not updated until patchSlot is called on them.
- data PatchChoices p wX wY
- patchChoices :: Patchy p => FL p wX wY -> PatchChoices p wX wY
- patchChoicesLps :: Patchy p => FL p wX wY -> (PatchChoices p wX wY, FL (LabelledPatch p) wX wY)
- patchChoicesLpsSub :: Patchy p => Maybe Label -> FL p wX wY -> (PatchChoices p wX wY, FL (LabelledPatch p) wX wY)
- patchSlot :: forall p wA wB wX wY. Patchy p => LabelledPatch p wA wB -> PatchChoices p wX wY -> (Slot, PatchChoices p wX wY)
- patchSlot' :: Patchy p => LabelledPatch p wA wB -> StateT (PatchChoices p wX wY) Identity Slot
- getChoices :: Patchy p => PatchChoices p wX wY -> (FL (LabelledPatch p) :> (FL (LabelledPatch p) :> FL (LabelledPatch p))) wX wY
- refineChoices :: (Patchy p, Monad m, Functor m) => (forall wU wV. FL (LabelledPatch p) wU wV -> PatchChoices p wU wV -> m (PatchChoices p wU wV)) -> PatchChoices p wX wY -> m (PatchChoices p wX wY)
- separateFirstMiddleFromLast :: Patchy p => PatchChoices p wX wZ -> (FL (LabelledPatch p) :> FL (LabelledPatch p)) wX wZ
- separateFirstFromMiddleLast :: Patchy p => PatchChoices p wX wZ -> (FL (LabelledPatch p) :> FL (LabelledPatch p)) wX wZ
- forceFirst :: Patchy p => Label -> PatchChoices p wA wB -> PatchChoices p wA wB
- forceFirsts :: Patchy p => [Label] -> PatchChoices p wA wB -> PatchChoices p wA wB
- forceLast :: Patchy p => Label -> PatchChoices p wA wB -> PatchChoices p wA wB
- forceLasts :: Patchy p => [Label] -> PatchChoices p wA wB -> PatchChoices p wA wB
- forceMatchingFirst :: forall p wA wB. Patchy p => (forall wX wY. LabelledPatch p wX wY -> Bool) -> PatchChoices p wA wB -> PatchChoices p wA wB
- forceMatchingLast :: Patchy p => (forall wX wY. LabelledPatch p wX wY -> Bool) -> PatchChoices p wA wB -> PatchChoices p wA wB
- selectAllMiddles :: forall p wX wY. Patchy p => Bool -> PatchChoices p wX wY -> PatchChoices p wX wY
- makeUncertain :: Patchy p => Label -> PatchChoices p wA wB -> PatchChoices p wA wB
- makeEverythingLater :: Patchy p => PatchChoices p wX wY -> PatchChoices p wX wY
- makeEverythingSooner :: forall p wX wY. Patchy p => PatchChoices p wX wY -> PatchChoices p wX wY
- data LabelledPatch p wX wY
- data Label
- label :: LabelledPatch p wX wY -> Label
- lpPatch :: LabelledPatch p wX wY -> p wX wY
- data Slot
- substitute :: forall p wX wY. Patchy p => Sealed2 (LabelledPatch p :||: FL (LabelledPatch p)) -> PatchChoices p wX wY -> PatchChoices p wX wY
Documentation
data PatchChoices p wX wY Source
patchChoices :: Patchy p => FL p wX wY -> PatchChoices p wX wY Source
patchChoicesLps :: Patchy p => FL p wX wY -> (PatchChoices p wX wY, FL (LabelledPatch p) wX wY) Source
Label a sequence of patches.
patchChoicesLpsSub :: Patchy p => Maybe Label -> FL p wX wY -> (PatchChoices p wX wY, FL (LabelledPatch p) wX wY) Source
Label a sequence of patches as subpatches of an existing label. This is intended for use when substituting a patch for an equivalent patch or patches.
patchSlot :: forall p wA wB wX wY. Patchy p => LabelledPatch p wA wB -> PatchChoices p wX wY -> (Slot, PatchChoices p wX wY) Source
patchSlot' :: Patchy p => LabelledPatch p wA wB -> StateT (PatchChoices p wX wY) Identity Slot Source
getChoices :: Patchy p => PatchChoices p wX wY -> (FL (LabelledPatch p) :> (FL (LabelledPatch p) :> FL (LabelledPatch p))) wX wY Source
getChoices evaluates a PatchChoices into the first, middle and last sequences
 by doing the commutes that were needed.
refineChoices :: (Patchy p, Monad m, Functor m) => (forall wU wV. FL (LabelledPatch p) wU wV -> PatchChoices p wU wV -> m (PatchChoices p wU wV)) -> PatchChoices p wX wY -> m (PatchChoices p wX wY) Source
refineChoices act performs act on the middle part of a sequence
 of choices, in order to hopefully get more patches into the first and
 last parts of a PatchChoices.
separateFirstMiddleFromLast :: Patchy p => PatchChoices p wX wZ -> (FL (LabelledPatch p) :> FL (LabelledPatch p)) wX wZ Source
separateFirstFromMiddleLast :: Patchy p => PatchChoices p wX wZ -> (FL (LabelledPatch p) :> FL (LabelledPatch p)) wX wZ Source
forceFirst :: Patchy p => Label -> PatchChoices p wA wB -> PatchChoices p wA wB Source
forceFirsts :: Patchy p => [Label] -> PatchChoices p wA wB -> PatchChoices p wA wB Source
forceLast :: Patchy p => Label -> PatchChoices p wA wB -> PatchChoices p wA wB Source
forceLasts :: Patchy p => [Label] -> PatchChoices p wA wB -> PatchChoices p wA wB Source
forceMatchingFirst :: forall p wA wB. Patchy p => (forall wX wY. LabelledPatch p wX wY -> Bool) -> PatchChoices p wA wB -> PatchChoices p wA wB Source
forceMatchingLast :: Patchy p => (forall wX wY. LabelledPatch p wX wY -> Bool) -> PatchChoices p wA wB -> PatchChoices p wA wB Source
selectAllMiddles :: forall p wX wY. Patchy p => Bool -> PatchChoices p wX wY -> PatchChoices p wX wY Source
makeUncertain :: Patchy p => Label -> PatchChoices p wA wB -> PatchChoices p wA wB Source
makeEverythingLater :: Patchy p => PatchChoices p wX wY -> PatchChoices p wX wY Source
makeEverythingSooner :: forall p wX wY. Patchy p => PatchChoices p wX wY -> PatchChoices p wX wY Source
data LabelledPatch p wX wY Source
Instances
| MyEq p => MyEq (LabelledPatch p) Source | |
| PatchInspect p => PatchInspect (LabelledPatch p) Source | |
| Invert p => Invert (LabelledPatch p) Source | |
| Commute p => Commute (LabelledPatch p) Source | |
| Merge p => Merge (LabelledPatch p) Source | 
Label mp i acts as a temporary identifier to help us keep track of patches
   during the selection process.  These are useful for finding patches that
   may have moved around during patch selection (being pushed forwards or
   backwards as dependencies arise).
The identifier is implemented as a tuple Label mp i. The i is just some
   arbitrary label, expected to be unique within the patches being
   scrutinised.  The mp is motivated by patch splitting; it
   provides a convenient way to generate a new identifier from the patch
   being split.  For example, if we split a patch identified as Label Nothing
   5, the resulting sub-patches could be identified as Label (Label Nothing 5)
   1, Label (Label Nothing 5) 2, etc.
label :: LabelledPatch p wX wY -> Label Source
lpPatch :: LabelledPatch p wX wY -> p wX wY Source
substitute :: forall p wX wY. Patchy p => Sealed2 (LabelledPatch p :||: FL (LabelledPatch p)) -> PatchChoices p wX wY -> PatchChoices p wX wY Source
substitute (a :||: bs) pcs replaces a with bs in pcs preserving the choice
   associated with a