darcs-2.18.2: a distributed, interactive, smart revision control system
Safe HaskellSafe-Inferred
LanguageHaskell2010

Darcs.UI.SelectChanges

Synopsis

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

Instances details
Show WhichChanges Source # 
Instance details

Defined in Darcs.UI.SelectChanges

Eq WhichChanges Source # 
Instance details

Defined in Darcs.UI.SelectChanges

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.

data SelectionConfig p Source #

All the static settings for selecting patches.

Interactive selection utils

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.

Constructors

ISC 

Fields

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.

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

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.

data KeyPress Source #

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

Constructors

KeyPress 

Fields

keysFor :: [[KeyPress]] -> [Char] Source #

The keys used by a list of keyPress groups.

helpFor :: String -> [[KeyPress]] -> [[KeyPress]] -> String Source #

Generates the help for a set of basic and advanced KeyPress groups.

askAboutDepends Source #

Arguments

:: (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.