Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data WhichChanges
- viewChanges :: (ShowPatch p, ShowContextPatch p, ApplyState p ~ Tree) => PatchSelectionOptions -> [Sealed2 p] -> IO ()
- withSelectedPatchFromList :: (Commute p, Matchable p, ShowPatch p, ShowContextPatch p, ApplyState p ~ Tree) => String -> RL p wX wY -> PatchSelectionOptions -> ((RL p :> p) wX wY -> IO ()) -> IO ()
- runSelection :: (MatchableRP p, ShowPatch p, ShowContextPatch p, ApplyState p ~ Tree, ApplyState p ~ ApplyState (PrimOf p)) => FL p wX wY -> SelectionConfig p -> IO ((FL p :> FL p) wX wY)
- runInvertibleSelection :: forall p wX wY. (Invert p, MatchableRP p, ShowPatch p, ShowContextPatch p, ApplyState p ~ Tree) => FL p wX wY -> SelectionConfig p -> IO ((FL p :> FL p) wX wY)
- selectionConfigPrim :: WhichChanges -> String -> PatchSelectionOptions -> Maybe (Splitter prim) -> Maybe [AnchoredPath] -> SelectionConfig prim
- selectionConfigGeneric :: Matchable p => (forall wX wY. q wX wY -> Sealed2 p) -> WhichChanges -> String -> PatchSelectionOptions -> Maybe [AnchoredPath] -> SelectionConfig q
- selectionConfig :: Matchable p => WhichChanges -> String -> PatchSelectionOptions -> Maybe (Splitter p) -> Maybe [AnchoredPath] -> SelectionConfig p
- data SelectionConfig p
- data PatchSelectionOptions = PatchSelectionOptions {}
- type InteractiveSelectionM p wX wY a = StateT (InteractiveSelectionState p wX wY) (PatchSelectionM p IO) a
- data InteractiveSelectionState p wX wY = ISC {
- total :: Int
- current :: Int
- lps :: FZipper (LabelledPatch p) wX wY
- choices :: PatchChoices p wX wY
- initialSelectionState :: FL (LabelledPatch p) wX wY -> PatchChoices p wX wY -> InteractiveSelectionState p wX wY
- currentPatch :: InteractiveSelectionM p wX wY (Maybe (Sealed2 (LabelledPatch p)))
- skipMundane :: (Commute p, ShowPatch p) => InteractiveSelectionM p wX wY ()
- skipOne :: InteractiveSelectionM p wX wY ()
- backOne :: InteractiveSelectionM p wX wY ()
- backAll :: InteractiveSelectionM p wX wY ()
- decide :: Commute p => Bool -> LabelledPatch p wA wB -> InteractiveSelectionM p wX wY ()
- decideWholeFile :: (Commute p, PatchInspect p) => AnchoredPath -> Bool -> InteractiveSelectionM p wX wY ()
- isSingleFile :: PatchInspect p => p wX wY -> Bool
- currentFile :: PatchInspect p => InteractiveSelectionM p wX wY (Maybe AnchoredPath)
- promptUser :: ShowPatch p => Bool -> Char -> InteractiveSelectionM p wX wY Char
- prompt :: ShowPatch p => InteractiveSelectionM p wX wY String
- data KeyPress = KeyPress {}
- keysFor :: [[KeyPress]] -> [Char]
- helpFor :: String -> [[KeyPress]] -> [[KeyPress]] -> String
- askAboutDepends :: (RepoPatch p, ApplyState p ~ Tree) => RL (PatchInfoAnd p) wX wR -> FL (PrimOf p) wR wT -> PatchSelectionOptions -> [PatchInfo] -> IO [PatchInfo]
Working with changes
data WhichChanges Source #
When asking about patches, we either ask about them in oldest-first or newest first (with respect to the current ordering of the repository), and we either want an initial segment or a final segment of the poset of patches.
First
: ask for an initial
segment, first patches first (default for all pull-like commands)
FirstReversed
: ask for an initial segment, last patches first
(used to ask about dependencies in record, and for pull-like
commands with the --reverse
flag).
LastReversed
: ask for a final segment, last patches first. (default
for unpull-like commands, except for selecting *primitive* patches in
rollback)
Last
: ask for a final segment, first patches first. (used for selecting
primitive patches in rollback, and for unpull-like commands with the
--reverse
flag
IOW: First = initial segment Last = final segment Reversed = start with the newest patch instead of oldest As usual, terminology is not, ahem, very intuitive.
Instances
Show WhichChanges Source # | |
Defined in Darcs.UI.SelectChanges showsPrec :: Int -> WhichChanges -> ShowS # show :: WhichChanges -> String # showList :: [WhichChanges] -> ShowS # | |
Eq WhichChanges Source # | |
Defined in Darcs.UI.SelectChanges (==) :: WhichChanges -> WhichChanges -> Bool # (/=) :: WhichChanges -> WhichChanges -> Bool # |
viewChanges :: (ShowPatch p, ShowContextPatch p, ApplyState p ~ Tree) => PatchSelectionOptions -> [Sealed2 p] -> IO () Source #
The equivalent of runSelection
for the darcs log
command
withSelectedPatchFromList :: (Commute p, Matchable p, ShowPatch p, ShowContextPatch p, ApplyState p ~ Tree) => String -> RL p wX wY -> PatchSelectionOptions -> ((RL p :> p) wX wY -> IO ()) -> IO () Source #
The function for selecting a patch to amend record. Read at your own risks.
runSelection :: (MatchableRP p, ShowPatch p, ShowContextPatch p, ApplyState p ~ Tree, ApplyState p ~ ApplyState (PrimOf p)) => FL p wX wY -> SelectionConfig p -> IO ((FL p :> FL p) wX wY) Source #
Run a PatchSelection
action in the given SelectionConfig
,
without assuming that patches are invertible.
runInvertibleSelection :: forall p wX wY. (Invert p, MatchableRP p, ShowPatch p, ShowContextPatch p, ApplyState p ~ Tree) => FL p wX wY -> SelectionConfig p -> IO ((FL p :> FL p) wX wY) Source #
Run a PatchSelection
action in the given SelectionConfig
,
assuming patches are invertible.
selectionConfigPrim :: WhichChanges -> String -> PatchSelectionOptions -> Maybe (Splitter prim) -> Maybe [AnchoredPath] -> SelectionConfig prim Source #
A SelectionConfig
for selecting Prim
patches.
selectionConfigGeneric :: Matchable p => (forall wX wY. q wX wY -> Sealed2 p) -> WhichChanges -> String -> PatchSelectionOptions -> Maybe [AnchoredPath] -> SelectionConfig q Source #
A generic SelectionConfig
.
selectionConfig :: Matchable p => WhichChanges -> String -> PatchSelectionOptions -> Maybe (Splitter p) -> Maybe [AnchoredPath] -> SelectionConfig p Source #
A SelectionConfig
for selecting full (Matchable
) patches
data SelectionConfig p Source #
All the static settings for selecting patches.
Interactive selection utils
data PatchSelectionOptions Source #
type InteractiveSelectionM p wX wY a = StateT (InteractiveSelectionState p wX wY) (PatchSelectionM p IO) a Source #
data InteractiveSelectionState p wX wY Source #
The dynamic parameters for interactive selection of patches.
ISC | |
|
initialSelectionState :: FL (LabelledPatch p) wX wY -> PatchChoices p wX wY -> InteractiveSelectionState p wX wY Source #
Navigating the patchset
currentPatch :: InteractiveSelectionM p wX wY (Maybe (Sealed2 (LabelledPatch p))) Source #
Returns a Sealed2
version of the patch we are asking the user
about.
skipMundane :: (Commute p, ShowPatch p) => InteractiveSelectionM p wX wY () Source #
Skips patches we should not ask the user about
skipOne :: InteractiveSelectionM p wX wY () Source #
Focus the next patch.
backOne :: InteractiveSelectionM p wX wY () Source #
Focus the previous patch.
backAll :: InteractiveSelectionM p wX wY () Source #
Decisions
decide :: Commute p => Bool -> LabelledPatch p wA wB -> InteractiveSelectionM p wX wY () Source #
decide True
selects the current patch, and decide False
deselects
it.
decideWholeFile :: (Commute p, PatchInspect p) => AnchoredPath -> Bool -> InteractiveSelectionM p wX wY () Source #
like decide
, but for all patches touching file
Prompts and queries
isSingleFile :: PatchInspect p => p wX wY -> Bool Source #
currentFile :: PatchInspect p => InteractiveSelectionM p wX wY (Maybe AnchoredPath) Source #
returns Just f
if the currentPatch
only modifies f
,
Nothing
otherwise.
promptUser :: ShowPatch p => Bool -> Char -> InteractiveSelectionM p wX wY Char Source #
Asks the user about one patch, returns their answer.
prompt :: ShowPatch p => InteractiveSelectionM p wX wY String Source #
The question to ask about one patch.
The type of the answers to a "shall I [wiggle] that [foo]?" question They are found in a [[KeyPress]] bunch, each list representing a set of answers which belong together
helpFor :: String -> [[KeyPress]] -> [[KeyPress]] -> String Source #
Generates the help for a set of basic and advanced KeyPress
groups.
:: (RepoPatch p, ApplyState p ~ Tree) | |
=> RL (PatchInfoAnd p) wX wR | patches to choose from |
-> FL (PrimOf p) wR wT | tentative content of new patch |
-> PatchSelectionOptions | |
-> [PatchInfo] | old explicit dependencies |
-> IO [PatchInfo] |
For a given sequence of preceding patches to choose from, and a sequence of prims which will become a new named patch, let the user select a subset such that the new patch will explicitly depend on them. The patches offered include only those that the new patch does not already depend on. To support amend, we pass in the old dependencies, too.