darcs-2.10.1: a distributed, interactive, smart revision control system

Safe HaskellNone
LanguageHaskell2010

Darcs.UI.SelectChanges

Contents

Synopsis

Working with changes

selectChanges :: forall p wX wY. (Patchy p, PatchInspect p, ShowPatch p, ApplyState p ~ Tree) => FL p wX wY -> PatchSelection p wX wY Source

Select patches from a FL.

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

viewChanges :: (Patchy p, ShowPatch p, ApplyState p ~ Tree) => PatchSelectionOptions -> [Sealed2 p] -> IO () Source

The equivalent of selectChanges for the darcs changes command

withSelectedPatchFromRepo :: forall p wR wU wT. (RepoPatch p, ApplyState p ~ Tree) => String -> Repository p wR wU wT -> PatchSelectionOptions -> (forall wA. (FL (PatchInfoAnd p) :> PatchInfoAnd p) wA wR -> IO ()) -> IO () Source

The function for selecting a patch to amend record. Read at your own risks.

runSelection :: Patchy p => PatchSelection p wX wY -> PatchSelectionContext p -> IO ((FL p :> FL p) wX wY) Source

runs a PatchSelection action in the given PatchSelectionContext.

data PatchSelectionContext p Source

A PatchSelectionContext contains all the static settings for selecting patches. See PatchSelectionM

printSummary :: forall p wX wY. ShowPatch p => p wX wY -> IO () Source

Interactive selection utils

type InteractiveSelectionM p wX wY a = StateT (InteractiveSelectionContext p wX wY) (PatchSelectionM p IO) a Source

data InteractiveSelectionContext p wX wY Source

The dynamic parameters for interactive selection of patches.

Constructors

ISC 

Fields

total :: Int

total number of patches

current :: Int

number of already-seen patches

lps :: FZipper (LabelledPatch p) wX wY

the patches we offer

choices :: PatchChoices p wX wY

the user's choices

Navigating the patchset

currentPatch :: forall p wX wY. Patchy p => InteractiveSelectionM p wX wY (Maybe (Sealed2 (LabelledPatch p))) Source

Returns a Sealed2 version of the patch we are asking the user about.

skipMundane :: (Patchy p, ShowPatch p) => InteractiveSelectionM p wX wY () Source

Skips patches we should not ask the user about

skipOne :: forall p wX wY. Patchy p => InteractiveSelectionM p wX wY () Source

Focus the next patch.

backOne :: forall p wX wY. Patchy p => InteractiveSelectionM p wX wY () Source

Focus the previous patch.

backAll :: forall p wX wY. Patchy p => InteractiveSelectionM p wX wY () Source

showCur :: forall p wX wY. (Patchy p, ShowPatch p, ApplyState p ~ Tree) => InteractiveSelectionM p wX wY () Source

Shows the current patch as it should be seen by the user.

Decisions

decide :: forall p wX wY wT wU. Patchy p => Bool -> LabelledPatch p wT wU -> InteractiveSelectionM p wX wY () Source

decide True selects the current patch, and decide False deselects it.

decideWholeFile :: forall p wX wY. (Patchy p, PatchInspect p) => FilePath -> Bool -> InteractiveSelectionM p wX wY () Source

like decide, but for all patches touching file

Prompts and queries

currentFile :: forall p wX wY. (Patchy p, PatchInspect p) => InteractiveSelectionM p wX wY (Maybe FilePath) Source

returns Just f if the currentPatch only modifies f, Nothing otherwise.

promptUser :: forall p wX wY. (Patchy p, ShowPatch p) => Bool -> Char -> InteractiveSelectionM p wX wY Char Source

Asks the user about one patch, returns their answer.

prompt :: (Patchy p, 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

kp :: Char
 
kpHelp :: String
 

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 :: forall p wR wU wT wY. (RepoPatch p, ApplyState p ~ Tree) => Repository p wR wU wT -> FL (PrimOf p) wT wY -> PatchSelectionOptions -> [PatchInfo] -> IO [PatchInfo] Source