Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
The purpose of this module is to deal with many of the common cases that come up when choosing a subset of a group of patches.
The idea is to divide a sequence of candidate patches into an initial
section named InFirst
, a final section named InLast
, and between them a
third section of not yet decided patches named InMiddle
. The reason for the
neutral terminology InFirst
, InMiddle
, and InLast
, is that which of InFirst
and InLast
counts as selected
or deselected
depends on
what we want to achive, that is, on the command and its options.
See Darcs.UI.SelectChanges for examples of how to use the functions from
this module.
Obviously if there are dependencies between the patches that will put a constraint on how you can choose to divide them up. Unless stated otherwise, functions that move patches from one section to another pull all dependent patches with them.
Internally, we don't necessarily reorder patches immediately, but merely tag them with the desired status, and thus postpone the actual commutation. This saves a lot of unnecessary work, especially when choices are made interactively, where the user can revise earlier decisions.
Synopsis
- data PatchChoices p wX wY
- data Slot
- patchChoices :: FL p wX wY -> PatchChoices p wX wY
- mkPatchChoices :: FL (LabelledPatch p) wX wY -> PatchChoices p wX wY
- patchSlot :: forall p wA wB wX wY. Commute p => LabelledPatch p wA wB -> PatchChoices p wX wY -> (Slot, PatchChoices p wX wY)
- getChoices :: Commute p => PatchChoices p wX wY -> (FL (LabelledPatch p) :> (FL (LabelledPatch p) :> FL (LabelledPatch p))) wX wY
- separateFirstMiddleFromLast :: Commute p => PatchChoices p wX wZ -> (FL (LabelledPatch p) :> FL (LabelledPatch p)) wX wZ
- separateFirstFromMiddleLast :: PatchChoices p wX wZ -> (FL (LabelledPatch p) :> FL (LabelledPatch p)) wX wZ
- forceMatchingFirst :: forall p wA wB. Commute p => (forall wX wY. LabelledPatch p wX wY -> Bool) -> PatchChoices p wA wB -> PatchChoices p wA wB
- forceFirsts :: Commute p => [Label] -> PatchChoices p wA wB -> PatchChoices p wA wB
- forceFirst :: Commute p => Label -> PatchChoices p wA wB -> PatchChoices p wA wB
- forceMatchingLast :: Commute p => (forall wX wY. LabelledPatch p wX wY -> Bool) -> PatchChoices p wA wB -> PatchChoices p wA wB
- forceLasts :: Commute p => [Label] -> PatchChoices p wA wB -> PatchChoices p wA wB
- forceLast :: Commute p => Label -> PatchChoices p wA wB -> PatchChoices p wA wB
- forceMiddle :: Commute p => Label -> PatchChoices p wA wB -> PatchChoices p wA wB
- makeEverythingSooner :: forall p wX wY. Commute p => PatchChoices p wX wY -> PatchChoices p wX wY
- makeEverythingLater :: PatchChoices p wX wY -> PatchChoices p wX wY
- selectAllMiddles :: forall p wX wY. Commute p => Bool -> PatchChoices p wX wY -> PatchChoices p wX wY
- refineChoices :: (Commute p, Monad 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)
- substitute :: forall p wX wY. Sealed2 (LabelledPatch p :||: FL (LabelledPatch p)) -> PatchChoices p wX wY -> PatchChoices p wX wY
- data LabelledPatch p wX wY
- data Label
- label :: LabelledPatch p wX wY -> Label
- unLabel :: LabelledPatch p wX wY -> p wX wY
- labelPatches :: Maybe Label -> FL p wX wY -> FL (LabelledPatch p) wX wY
- getLabelInt :: Label -> Int
Choosing patches
data PatchChoices p wX wY Source #
A sequence of LabelledPatch
es where each patch is either
InFirst
, InMiddle
, or InLast
. The representation is
optimized for the case where we start chosing patches from the left
of the sequence: patches that are InFirst
are commuted to the head
immediately, but patches that are InMiddle
or InLast
are mixed
together; when a patch is marked InLast
, its dependencies are
not updated until we retrieve the final result.
Constructing
patchChoices :: FL p wX wY -> PatchChoices p wX wY Source #
Create a PatchChoices
from a sequence of patches, so that
all patches are initially InMiddle
.
mkPatchChoices :: FL (LabelledPatch p) wX wY -> PatchChoices p wX wY Source #
Create a PatchChoices
from an already labelled sequence of patches,
so that all patches are initially InMiddle
.
Querying
patchSlot :: forall p wA wB wX wY. Commute p => LabelledPatch p wA wB -> PatchChoices p wX wY -> (Slot, PatchChoices p wX wY) Source #
Given a LabelledPatch
determine to which section of the given
PatchChoices
it belongs. This is not trivial to compute, since a patch
tagged as InMiddle
may be forced to actually be InLast
by dependencies. We
return a possibly re-ordered PatchChoices
so as not to waste the
commutation effort.
getChoices :: Commute p => PatchChoices p wX wY -> (FL (LabelledPatch p) :> (FL (LabelledPatch p) :> FL (LabelledPatch p))) wX wY Source #
separateFirstMiddleFromLast :: Commute p => PatchChoices p wX wZ -> (FL (LabelledPatch p) :> FL (LabelledPatch p)) wX wZ Source #
Like getChoices
but lumps together InFirst
and InMiddle
patches.
separateFirstMiddleFromLast c == case getChoices c of f:>m:>l -> f+>+m:>l
separateFirstFromMiddleLast :: PatchChoices p wX wZ -> (FL (LabelledPatch p) :> FL (LabelledPatch p)) wX wZ Source #
Like getChoices
but lumps together InMiddle
and InLast
patches.
This is more efficient than using getChoices
and then catenating InMiddle
and InLast
sections because we have to commute less.
(This is what PatchChoices
are optimized for.)
separateFirstFromMiddleLast c == case getChoices c of f:>m:>l -> f:>m+>+l
Forcing patches into a given Slot
forceMatchingFirst :: forall p wA wB. Commute p => (forall wX wY. LabelledPatch p wX wY -> Bool) -> PatchChoices p wA wB -> PatchChoices p wA wB Source #
forceFirsts :: Commute p => [Label] -> PatchChoices p wA wB -> PatchChoices p wA wB Source #
forceFirst :: Commute p => Label -> PatchChoices p wA wB -> PatchChoices p wA wB Source #
forceMatchingLast :: Commute p => (forall wX wY. LabelledPatch p wX wY -> Bool) -> PatchChoices p wA wB -> PatchChoices p wA wB Source #
Similar to forceMatchingFirst
only that patches are forced to be
InLast
regardless of their previous status.
forceLasts :: Commute p => [Label] -> PatchChoices p wA wB -> PatchChoices p wA wB Source #
forceLast :: Commute p => Label -> PatchChoices p wA wB -> PatchChoices p wA wB Source #
Force a single patch labelled with the given label to be InLast
,
pulling any dependencies with them, regardless of their previous status.
forceMiddle :: Commute p => Label -> PatchChoices p wA wB -> PatchChoices p wA wB Source #
makeEverythingSooner :: forall p wX wY. Commute p => PatchChoices p wX wY -> PatchChoices p wX wY Source #
makeEverythingLater :: PatchChoices p wX wY -> PatchChoices p wX wY Source #
Operations on InMiddle
patches
selectAllMiddles :: forall p wX wY. Commute p => Bool -> PatchChoices p wX wY -> PatchChoices p wX wY Source #
refineChoices :: (Commute p, Monad 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 #
Use the given monadic PatchChoices
transformer on the InMiddle
section
of a PatchChoices
, then fold the result back into the original PatchChoices
.
Substitution
substitute :: forall p wX wY. Sealed2 (LabelledPatch p :||: FL (LabelledPatch p)) -> PatchChoices p wX wY -> PatchChoices p wX wY Source #
Substitute a single LabelledPatch
with an equivalent list of patches,
preserving its status as InFirst
, InMiddle
or InLast
).
The patch is looked up using equality of Label
s.
Labelling patches
data LabelledPatch p wX wY Source #
A patch with a Label
attached to it.
Instances
Commute p => Commute (LabelledPatch p) Source # | |
Defined in Darcs.Patch.Choices commute :: (LabelledPatch p :> LabelledPatch p) wX wY -> Maybe ((LabelledPatch p :> LabelledPatch p) wX wY) Source # | |
PatchInspect p => PatchInspect (LabelledPatch p) Source # | |
Defined in Darcs.Patch.Choices listTouchedFiles :: LabelledPatch p wX wY -> [AnchoredPath] Source # hunkMatches :: (ByteString -> Bool) -> LabelledPatch p wX wY -> Bool Source # | |
Invert p => Invert (LabelledPatch p) Source # | |
Defined in Darcs.Patch.Choices invert :: LabelledPatch p wX wY -> LabelledPatch p wY wX 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 an
integer, 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 (Just (Label Nothing 5))1
, Label (Just (Label Nothing 5)) 2
, etc.
label :: LabelledPatch p wX wY -> Label Source #
unLabel :: LabelledPatch p wX wY -> p wX wY Source #
labelPatches :: Maybe Label -> FL p wX wY -> FL (LabelledPatch p) wX wY Source #
Label a sequence of patches, maybe using the given parent label.
getLabelInt :: Label -> Int Source #