{-# LANGUAGE OverloadedStrings #-}
module Darcs.UI.Commands.WhatsNew
( whatsnew
, status
) where
import Darcs.Prelude
import Control.Monad ( void, when )
import Control.Monad.Reader ( runReaderT )
import Control.Monad.State ( evalStateT, liftIO )
import System.Exit ( ExitCode (..), exitSuccess, exitWith )
import Darcs.Patch
( PrimOf, PrimPatch, RepoPatch
, applyToTree, plainSummaryPrims, primIsHunk
)
import Darcs.Patch.Apply ( ApplyState )
import Darcs.Patch.Choices ( mkPatchChoices, labelPatches, unLabel )
import Darcs.Patch.Commute ( Commute )
import Darcs.Patch.FileHunk ( IsHunk (..) )
import Darcs.Patch.Inspect ( PatchInspect (..) )
import Darcs.Patch.Permutations ( partitionRL )
import Darcs.Patch.Prim.Class ( PrimDetails (..) )
import Darcs.Patch.Show
( ShowContextPatch
, ShowPatch(..)
, ShowPatchBasic(..)
, displayPatch
)
import Darcs.Patch.TouchesFiles ( chooseTouching )
import Darcs.Patch.Witnesses.Ordered
( (:>) (..), FL (..)
, reverseFL, reverseRL
)
import Darcs.Patch.Witnesses.Sealed
( Sealed (..), Sealed2 (..)
, unFreeLeft
)
import Darcs.Repository
( RepoJob (..), Repository
, readRecorded
, unrecordedChanges, withRepository
)
import Darcs.Repository.Diff ( treeDiff )
import Darcs.Repository.Prefs ( filetypeFunction )
import Darcs.UI.Commands
( DarcsCommand(..), withStdOpts, amInRepository
, commandAlias, nodefaults
)
import Darcs.UI.Completion ( modifiedFileArgs )
import Darcs.UI.Commands.Util ( announceFiles, filterExistingPaths )
import Darcs.UI.External ( viewDocWith )
import Darcs.UI.Flags
( DarcsFlag, diffAlgorithm
, withContext, useCache, pathSetFromArgs
, verbosity, isInteractive
, lookForAdds, lookForMoves, lookForReplaces
, scanKnown, useIndex, diffingOpts
)
import Darcs.UI.Options
( DarcsOption, (^), odesc, ocheck, defaultFlags, parseFlags, (?) )
import qualified Darcs.UI.Options.All as O
import Darcs.UI.PrintPatch ( contextualPrintPatch )
import Darcs.UI.SelectChanges
( InteractiveSelectionM, KeyPress (..)
, WhichChanges (..)
, initialSelectionState
, backAll
, backOne, currentFile
, currentPatch, decide
, decideWholeFile, helpFor
, keysFor, prompt
, selectionConfigPrim, skipMundane
, skipOne
)
import qualified Darcs.UI.SelectChanges as S ( PatchSelectionOptions (..) )
import Darcs.Util.Path ( AbsolutePath, AnchoredPath )
import Darcs.Util.Printer
( Doc, formatWords, putDocLn, renderString
, text, vcat, ($+$)
)
import Darcs.Util.Printer.Color ( fancyPrinters )
import Darcs.Util.Prompt ( PromptConfig (..), promptChar )
import Darcs.Util.Tree ( Tree )
commonAdvancedOpts :: DarcsOption a (O.UseIndex -> O.IncludeBoring -> a)
commonAdvancedOpts :: DarcsOption a (UseIndex -> IncludeBoring -> a)
commonAdvancedOpts = PrimOptSpec DarcsOptDescr Flag (IncludeBoring -> a) UseIndex
PrimDarcsOption UseIndex
O.useIndex PrimOptSpec DarcsOptDescr Flag (IncludeBoring -> a) UseIndex
-> OptSpec DarcsOptDescr Flag a (IncludeBoring -> a)
-> DarcsOption a (UseIndex -> IncludeBoring -> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec DarcsOptDescr Flag a (IncludeBoring -> a)
PrimDarcsOption IncludeBoring
O.includeBoring
patchSelOpts :: [DarcsFlag] -> S.PatchSelectionOptions
patchSelOpts :: [Flag] -> PatchSelectionOptions
patchSelOpts [Flag]
flags = PatchSelectionOptions :: Verbosity
-> [MatchFlag]
-> Bool
-> SelectDeps
-> WithSummary
-> WithContext
-> PatchSelectionOptions
S.PatchSelectionOptions
{ verbosity :: Verbosity
S.verbosity = PrimDarcsOption Verbosity
verbosity PrimDarcsOption Verbosity -> [Flag] -> Verbosity
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [Flag]
flags
, matchFlags :: [MatchFlag]
S.matchFlags = []
, interactive :: Bool
S.interactive = Bool -> [Flag] -> Bool
isInteractive Bool
True [Flag]
flags
, selectDeps :: SelectDeps
S.selectDeps = SelectDeps
O.PromptDeps
, withSummary :: WithSummary
S.withSummary = [Flag] -> WithSummary
getSummary [Flag]
flags
, withContext :: WithContext
S.withContext = PrimDarcsOption WithContext
withContext PrimDarcsOption WithContext -> [Flag] -> WithContext
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [Flag]
flags
}
getSummary :: [DarcsFlag] -> O.WithSummary
getSummary :: [Flag] -> WithSummary
getSummary [Flag]
flags = case Maybe WithSummary
-> forall a. PrimOptSpec DarcsOptDescr Flag a (Maybe WithSummary)
O.maybeSummary Maybe WithSummary
forall a. Maybe a
Nothing (forall a. PrimOptSpec DarcsOptDescr Flag a (Maybe WithSummary))
-> [Flag] -> Maybe WithSummary
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [Flag]
flags of
Just WithSummary
O.NoSummary -> WithSummary
O.NoSummary
Just WithSummary
O.YesSummary -> WithSummary
O.YesSummary
Maybe WithSummary
Nothing
| LookForAdds -> Bool
forall a. YesNo a => a -> Bool
O.yes ([Flag] -> LookForAdds
lookForAdds [Flag]
flags) -> WithSummary
O.YesSummary
| PrimDarcsOption Bool
O.machineReadable PrimDarcsOption Bool -> [Flag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [Flag]
flags -> WithSummary
O.YesSummary
| Bool
otherwise -> WithSummary
O.NoSummary
whatsnew :: DarcsCommand
whatsnew :: DarcsCommand
whatsnew = DarcsCommand :: String
-> String
-> Doc
-> String
-> Int
-> [String]
-> ((AbsolutePath, AbsolutePath) -> [Flag] -> [String] -> IO ())
-> ([Flag] -> IO (Either String ()))
-> ((AbsolutePath, AbsolutePath)
-> [Flag] -> [String] -> IO [String])
-> ([Flag] -> AbsolutePath -> [String] -> IO [String])
-> [DarcsOptDescr Flag]
-> [DarcsOptDescr Flag]
-> [Flag]
-> ([Flag] -> [String])
-> DarcsCommand
DarcsCommand
{ commandProgramName :: String
commandProgramName = String
"darcs"
, commandName :: String
commandName = String
"whatsnew"
, commandHelp :: Doc
commandHelp = Doc
whatsnewHelp
, commandDescription :: String
commandDescription = String
whatsnewDescription
, commandExtraArgs :: Int
commandExtraArgs = -Int
1
, commandExtraArgHelp :: [String]
commandExtraArgHelp = [String
"[FILE or DIRECTORY]..."]
, commandCommand :: (AbsolutePath, AbsolutePath) -> [Flag] -> [String] -> IO ()
commandCommand = (AbsolutePath, AbsolutePath) -> [Flag] -> [String] -> IO ()
whatsnewCmd
, commandPrereq :: [Flag] -> IO (Either String ())
commandPrereq = [Flag] -> IO (Either String ())
amInRepository
, commandCompleteArgs :: (AbsolutePath, AbsolutePath) -> [Flag] -> [String] -> IO [String]
commandCompleteArgs = (AbsolutePath, AbsolutePath) -> [Flag] -> [String] -> IO [String]
modifiedFileArgs
, commandArgdefaults :: [Flag] -> AbsolutePath -> [String] -> IO [String]
commandArgdefaults = [Flag] -> AbsolutePath -> [String] -> IO [String]
nodefaults
, commandAdvancedOptions :: [DarcsOptDescr Flag]
commandAdvancedOptions = OptSpec DarcsOptDescr Flag Any (UseIndex -> IncludeBoring -> Any)
-> [DarcsOptDescr Flag]
forall (d :: * -> *) f a b. OptSpec d f a b -> [d f]
odesc OptSpec DarcsOptDescr Flag Any (UseIndex -> IncludeBoring -> Any)
forall a. DarcsOption a (UseIndex -> IncludeBoring -> a)
commonAdvancedOpts
, commandBasicOptions :: [DarcsOptDescr Flag]
commandBasicOptions = OptSpec
DarcsOptDescr
Flag
Any
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Any)
-> [DarcsOptDescr Flag]
forall (d :: * -> *) f a b. OptSpec d f a b -> [d f]
odesc OptSpec
DarcsOptDescr
Flag
Any
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Any)
forall a.
OptSpec
DarcsOptDescr
Flag
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
whatsnewBasicOpts
, commandDefaults :: [Flag]
commandDefaults = OptSpec
DarcsOptDescr
Flag
[Flag]
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> [Flag])
-> [Flag]
forall (d :: * -> *) f b. OptSpec d f [f] b -> [f]
defaultFlags OptSpec
DarcsOptDescr
Flag
[Flag]
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> [Flag])
forall a.
DarcsOption
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
whatsnewOpts
, commandCheckOptions :: [Flag] -> [String]
commandCheckOptions = OptSpec
DarcsOptDescr
Flag
Any
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> Any)
-> [Flag] -> [String]
forall (d :: * -> *) f a b. OptSpec d f a b -> [f] -> [String]
ocheck OptSpec
DarcsOptDescr
Flag
Any
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> Any)
forall a.
DarcsOption
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
whatsnewOpts
}
where
whatsnewBasicOpts :: OptSpec
DarcsOptDescr
Flag
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
whatsnewBasicOpts
= Maybe WithSummary
-> forall a. PrimOptSpec DarcsOptDescr Flag a (Maybe WithSummary)
O.maybeSummary Maybe WithSummary
forall a. Maybe a
Nothing
PrimOptSpec
DarcsOptDescr
Flag
(WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
(Maybe WithSummary)
-> OptSpec
DarcsOptDescr
Flag
(Bool
-> LookFor -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Bool
-> LookFor -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
Flag
(Bool
-> LookFor -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
PrimDarcsOption WithContext
O.withContext
OptSpec
DarcsOptDescr
Flag
(Bool
-> LookFor -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(LookFor -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(Bool
-> LookFor -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
Flag
(LookFor -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
Flag
(LookFor -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(Bool
-> LookFor -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
PrimDarcsOption Bool
O.machineReadable
OptSpec
DarcsOptDescr
Flag
(LookFor -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(LookFor -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
Flag
(DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
Flag
(DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(LookFor -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
PrimDarcsOption LookFor
O.lookfor
OptSpec
DarcsOptDescr
Flag
(DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe String -> Maybe Bool -> a)
(DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
Flag
(Maybe String -> Maybe Bool -> a)
(DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
PrimDarcsOption DiffAlgorithm
O.diffAlgorithm
OptSpec
DarcsOptDescr
Flag
(Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe Bool -> a)
(Maybe String -> Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
Flag
(Maybe Bool -> a)
(Maybe String -> Maybe Bool -> a)
PrimDarcsOption (Maybe String)
O.repoDir
OptSpec
DarcsOptDescr
Flag
(Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec DarcsOptDescr Flag a (Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
Flag
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec DarcsOptDescr Flag a (Maybe Bool -> a)
PrimDarcsOption (Maybe Bool)
O.interactive
whatsnewOpts :: DarcsOption
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
whatsnewOpts = OptSpec
DarcsOptDescr
Flag
(Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
forall a.
OptSpec
DarcsOptDescr
Flag
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
whatsnewBasicOpts OptSpec
DarcsOptDescr
Flag
(Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
-> DarcsOption
(UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
(UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
-> DarcsOption
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookFor
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
forall b c a.
DarcsOption (Maybe StdCmdAction -> Verbosity -> b) c
-> DarcsOption
(UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a) b
-> DarcsOption a c
`withStdOpts` DarcsOption
(UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
(UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
forall a. DarcsOption a (UseIndex -> IncludeBoring -> a)
commonAdvancedOpts
whatsnewDescription :: String
whatsnewDescription :: String
whatsnewDescription = String
"List unrecorded changes in the working tree."
whatsnewHelp :: Doc
whatsnewHelp :: Doc
whatsnewHelp =
[String] -> Doc
formatWords
[ String
"The `darcs whatsnew` command lists unrecorded changes to the working"
, String
"tree. If you specify a set of files and directories, only unrecorded"
, String
"changes to those files and directories are listed."
]
Doc -> Doc -> Doc
$+$ [String] -> Doc
formatWords
[ String
"With the `--summary` option, the changes are condensed to one line per"
, String
"file, with mnemonics to indicate the nature and extent of the change."
, String
"The `--look-for-adds` option causes candidates for `darcs add` to be"
, String
"included in the summary output. WithSummary mnemonics are as follows:"
]
Doc -> Doc -> Doc
$+$ [Doc] -> Doc
vcat
[ Doc
" * `A f` and `A d/` respectively mean an added file or directory."
, Doc
" * `R f` and `R d/` respectively mean a removed file or directory."
, Doc
" * `M f -N +M rP` means a modified file, with `N` lines deleted, `M`"
, Doc
" lines added, and `P` lexical replacements."
, Doc
" * `f -> g` means a moved file or directory."
, Doc
" * `a f` and `a d/` respectively mean a new, but unadded, file or"
, Doc
" directory, when using `--look-for-adds`."
, Doc
" * An exclamation mark (!) as in `R! foo.c`, means the change"
, Doc
" conflicts with a change in an earlier patch. The phrase `duplicated`"
, Doc
" means the change is identical to a change in an earlier patch."
]
Doc -> Doc -> Doc
$+$ [String] -> Doc
formatWords
[ String
"The `--machine-readable` option implies `--summary` while making it more"
, String
"parsable. Modified files are only shown as `M f`, and moves are shown in"
, String
"two lines: `F f` and `T g` (as in 'From f To g')."
]
Doc -> Doc -> Doc
$+$ [String] -> Doc
formatWords
[ String
"By default, `darcs whatsnew` uses Darcs' internal format for changes."
, String
"To see some context (unchanged lines) around each change, use the"
, String
"`--unified` option. To view changes in conventional `diff` format, use"
, String
"the `darcs diff` command; but note that `darcs whatsnew` is faster."
]
Doc -> Doc -> Doc
$+$ [String] -> Doc
formatWords
[ String
"This command exits unsuccessfully (returns a non-zero exit status) if"
, String
"there are no unrecorded changes."
]
whatsnewCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
whatsnewCmd :: (AbsolutePath, AbsolutePath) -> [Flag] -> [String] -> IO ()
whatsnewCmd (AbsolutePath, AbsolutePath)
fps [Flag]
opts [String]
args =
UseCache -> RepoJob () -> IO ()
forall a. UseCache -> RepoJob a -> IO a
withRepository (PrimDarcsOption UseCache
useCache PrimDarcsOption UseCache -> [Flag] -> UseCache
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [Flag]
opts) (RepoJob () -> IO ()) -> RepoJob () -> IO ()
forall a b. (a -> b) -> a -> b
$ (forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
(IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wR wU wR -> IO ())
-> RepoJob ()
forall a.
(forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
(IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wR wU wR -> IO a)
-> RepoJob a
RepoJob ((forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
(IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wR wU wR -> IO ())
-> RepoJob ())
-> (forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
(IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wR wU wR -> IO ())
-> RepoJob ()
forall a b. (a -> b) -> a -> b
$ \(Repository rt p wR wU wR
repo :: Repository rt p wR wU wR) -> do
let scan :: ScanKnown
scan = LookForAdds -> IncludeBoring -> ScanKnown
scanKnown ([Flag] -> LookForAdds
lookForAdds [Flag]
opts) (PrimDarcsOption IncludeBoring
O.includeBoring PrimDarcsOption IncludeBoring -> [Flag] -> IncludeBoring
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [Flag]
opts)
Maybe [AnchoredPath]
existing_files <- do
Maybe [AnchoredPath]
files <- (AbsolutePath, AbsolutePath)
-> [String] -> IO (Maybe [AnchoredPath])
pathSetFromArgs (AbsolutePath, AbsolutePath)
fps [String]
args
Maybe ([AnchoredPath], [AnchoredPath])
files' <- ([AnchoredPath] -> IO ([AnchoredPath], [AnchoredPath]))
-> Maybe [AnchoredPath]
-> IO (Maybe ([AnchoredPath], [AnchoredPath]))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse
(Repository rt p wR wU wR
-> Verbosity
-> UseIndex
-> ScanKnown
-> LookForMoves
-> [AnchoredPath]
-> IO ([AnchoredPath], [AnchoredPath])
forall (p :: * -> * -> *) (rt :: RepoType) wR wU.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wR wU wR
-> Verbosity
-> UseIndex
-> ScanKnown
-> LookForMoves
-> [AnchoredPath]
-> IO ([AnchoredPath], [AnchoredPath])
filterExistingPaths
Repository rt p wR wU wR
repo (PrimDarcsOption Verbosity
verbosity PrimDarcsOption Verbosity -> [Flag] -> Verbosity
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [Flag]
opts) (PrimDarcsOption UseIndex
useIndex PrimDarcsOption UseIndex -> [Flag] -> UseIndex
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [Flag]
opts) ScanKnown
scan ([Flag] -> LookForMoves
lookForMoves [Flag]
opts))
Maybe [AnchoredPath]
files
let files'' :: Maybe [AnchoredPath]
files'' = (([AnchoredPath], [AnchoredPath]) -> [AnchoredPath])
-> Maybe ([AnchoredPath], [AnchoredPath]) -> Maybe [AnchoredPath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([AnchoredPath], [AnchoredPath]) -> [AnchoredPath]
forall a b. (a, b) -> b
snd Maybe ([AnchoredPath], [AnchoredPath])
files'
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe [AnchoredPath]
files'' Maybe [AnchoredPath] -> Maybe [AnchoredPath] -> Bool
forall a. Eq a => a -> a -> Bool
== [AnchoredPath] -> Maybe [AnchoredPath]
forall a. a -> Maybe a
Just []) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
String -> IO ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"None of the files you specified exist."
Maybe [AnchoredPath] -> IO (Maybe [AnchoredPath])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [AnchoredPath]
files''
Sealed FL (PrimOf p) wR wX
allInterestingChanges <-
(UseIndex, ScanKnown, DiffAlgorithm)
-> LookForMoves
-> LookForReplaces
-> Repository rt p wR wU wR
-> Maybe [AnchoredPath]
-> IO (Sealed (FL (PrimOf p) wR))
forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
(RepoPatch p, ApplyState p ~ Tree) =>
(UseIndex, ScanKnown, DiffAlgorithm)
-> LookForMoves
-> LookForReplaces
-> Repository rt p wR wU wR
-> Maybe [AnchoredPath]
-> IO (Sealed (FL (PrimOf p) wR))
filteredUnrecordedChanges ([Flag] -> (UseIndex, ScanKnown, DiffAlgorithm)
diffingOpts [Flag]
opts)
([Flag] -> LookForMoves
lookForMoves [Flag]
opts) ([Flag] -> LookForReplaces
lookForReplaces [Flag]
opts)
Repository rt p wR wU wR
repo Maybe [AnchoredPath]
existing_files
Tree IO
pristine <- Repository rt p wR wU wR -> IO (Tree IO)
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
Repository rt p wR wU wT -> IO (Tree IO)
readRecorded Repository rt p wR wU wR
repo
Sealed FL (PrimOf p) wR wX
noLookChanges <-
if Bool
haveLookForAddsAndSummary
then
(UseIndex, ScanKnown, DiffAlgorithm)
-> LookForMoves
-> LookForReplaces
-> Repository rt p wR wU wR
-> Maybe [AnchoredPath]
-> IO (Sealed (FL (PrimOf p) wR))
forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
(RepoPatch p, ApplyState p ~ Tree) =>
(UseIndex, ScanKnown, DiffAlgorithm)
-> LookForMoves
-> LookForReplaces
-> Repository rt p wR wU wR
-> Maybe [AnchoredPath]
-> IO (Sealed (FL (PrimOf p) wR))
filteredUnrecordedChanges (PrimDarcsOption UseIndex
O.useIndex PrimDarcsOption UseIndex -> [Flag] -> UseIndex
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [Flag]
opts, ScanKnown
O.ScanKnown, PrimDarcsOption DiffAlgorithm
O.diffAlgorithm PrimDarcsOption DiffAlgorithm -> [Flag] -> DiffAlgorithm
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [Flag]
opts)
([Flag] -> LookForMoves
lookForMoves [Flag]
opts) ([Flag] -> LookForReplaces
lookForReplaces [Flag]
opts)
Repository rt p wR wU wR
repo Maybe [AnchoredPath]
existing_files
else Sealed (FL (PrimOf p) wR) -> IO (Sealed (FL (PrimOf p) wR))
forall (m :: * -> *) a. Monad m => a -> m a
return (FL (PrimOf p) wR wR -> Sealed (FL (PrimOf p) wR)
forall (a :: * -> *) wX. a wX -> Sealed a
Sealed FL (PrimOf p) wR wR
forall (a :: * -> * -> *) wX. FL a wX wX
NilFL)
Sealed FL (PrimOf p) Any wX
unaddedNewPathsPs <-
if Bool
haveLookForAddsAndSummary
then do
Tree IO
noLookAddsTree <- FL (PrimOf p) wR wX -> Tree IO -> IO (Tree IO)
forall (m :: * -> *) (p :: * -> * -> *) wX wY.
(Commute p, PrimClassify p, Apply p, Monad m,
ApplyState p ~ Tree) =>
FL p wX wY -> Tree m -> m (Tree m)
applyAddPatchesToPristine FL (PrimOf p) wR wX
noLookChanges Tree IO
pristine
Tree IO
lookAddsTree <- FL (PrimOf p) wR wX -> Tree IO -> IO (Tree IO)
forall (m :: * -> *) (p :: * -> * -> *) wX wY.
(Commute p, PrimClassify p, Apply p, Monad m,
ApplyState p ~ Tree) =>
FL p wX wY -> Tree m -> m (Tree m)
applyAddPatchesToPristine FL (PrimOf p) wR wX
allInterestingChanges Tree IO
pristine
String -> FileType
ftf <- IO (String -> FileType)
filetypeFunction
FreeLeft (FL (PrimOf p)) -> Sealed (FL (PrimOf p) Any)
forall (p :: * -> * -> *) wX. FreeLeft p -> Sealed (p wX)
unFreeLeft (FreeLeft (FL (PrimOf p)) -> Sealed (FL (PrimOf p) Any))
-> IO (FreeLeft (FL (PrimOf p))) -> IO (Sealed (FL (PrimOf p) Any))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DiffAlgorithm
-> (String -> FileType)
-> Tree IO
-> Tree IO
-> IO (FreeLeft (FL (PrimOf p)))
forall (m :: * -> *) (w :: (* -> * -> *) -> *)
(prim :: * -> * -> *).
(Monad m, Gap w, PrimPatch prim) =>
DiffAlgorithm
-> (String -> FileType) -> Tree m -> Tree m -> m (w (FL prim))
treeDiff (PrimDarcsOption DiffAlgorithm
diffAlgorithm PrimDarcsOption DiffAlgorithm -> [Flag] -> DiffAlgorithm
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [Flag]
opts) String -> FileType
ftf Tree IO
noLookAddsTree Tree IO
lookAddsTree
else Sealed (FL (PrimOf p) Any) -> IO (Sealed (FL (PrimOf p) Any))
forall (m :: * -> *) a. Monad m => a -> m a
return (FL (PrimOf p) Any Any -> Sealed (FL (PrimOf p) Any)
forall (a :: * -> *) wX. a wX -> Sealed a
Sealed FL (PrimOf p) Any Any
forall (a :: * -> * -> *) wX. FL a wX wX
NilFL)
FL (PrimOf p) wR wX -> FL (PrimOf p) Any wX -> IO ()
forall (p :: * -> * -> *) wX wY wU wV.
FL p wX wY -> FL p wU wV -> IO ()
samePatchType FL (PrimOf p) wR wX
noLookChanges FL (PrimOf p) Any wX
unaddedNewPathsPs
FL (PrimOf p) wR wX -> IO ()
forall (p :: * -> * -> *) wX wY. FL p wX wY -> IO ()
exitOnNoChanges FL (PrimOf p) wR wX
allInterestingChanges
Verbosity -> Maybe [AnchoredPath] -> String -> IO ()
announceFiles (PrimDarcsOption Verbosity
verbosity PrimDarcsOption Verbosity -> [Flag] -> Verbosity
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [Flag]
opts) Maybe [AnchoredPath]
existing_files String
"What's new in"
if [Flag] -> Bool
maybeIsInteractive [Flag]
opts
then
InteractiveSelectionM (PrimOf p) wR wX ()
-> PatchSelectionOptions -> Tree IO -> FL (PrimOf p) wR wX -> IO ()
forall (p :: * -> * -> *) wX wY.
InteractiveSelectionM p wX wY ()
-> PatchSelectionOptions -> Tree IO -> FL p wX wY -> IO ()
runInteractive (Tree IO -> InteractiveSelectionM (PrimOf p) wR wX ()
forall (p :: * -> * -> *) wX wY.
(IsHunk p, ShowPatch p, ShowContextPatch p, Commute p,
PatchInspect p, PrimDetails p, ApplyState p ~ Tree) =>
Tree IO -> InteractiveSelectionM p wX wY ()
interactiveHunks Tree IO
pristine) ([Flag] -> PatchSelectionOptions
patchSelOpts [Flag]
opts)
Tree IO
pristine FL (PrimOf p) wR wX
allInterestingChanges
else
if Bool
haveLookForAddsAndSummary
then do
Tree IO -> FL (PrimOf p) wR wX -> IO ()
forall (p :: * -> * -> *) wX wY.
(PrimPatch p, ApplyState p ~ Tree) =>
Tree IO -> FL p wX wY -> IO ()
printChanges Tree IO
pristine FL (PrimOf p) wR wX
noLookChanges
FL (PrimOf p) Any wX -> IO ()
forall (p :: * -> * -> *) wX wY. PrimPatch p => FL p wX wY -> IO ()
printUnaddedPaths FL (PrimOf p) Any wX
unaddedNewPathsPs
else do
Tree IO -> FL (PrimOf p) wR wX -> IO ()
forall (p :: * -> * -> *) wX wY.
(PrimPatch p, ApplyState p ~ Tree) =>
Tree IO -> FL p wX wY -> IO ()
printChanges Tree IO
pristine FL (PrimOf p) wR wX
allInterestingChanges
where
haveSummary :: Bool
haveSummary = WithSummary -> Bool
forall a. YesNo a => a -> Bool
O.yes ([Flag] -> WithSummary
getSummary [Flag]
opts)
haveLookForAddsAndSummary :: Bool
haveLookForAddsAndSummary = Bool
haveSummary Bool -> Bool -> Bool
&& LookForAdds -> Bool
forall a. YesNo a => a -> Bool
O.yes ([Flag] -> LookForAdds
lookForAdds [Flag]
opts)
applyAddPatchesToPristine :: FL p wX wY -> Tree m -> m (Tree m)
applyAddPatchesToPristine FL p wX wY
ps Tree m
pristine = do
RL p wX wZ
adds :> RL p wZ wY
_ <- (:>) (RL p) (RL p) wX wY -> m ((:>) (RL p) (RL p) wX wY)
forall (m :: * -> *) a. Monad m => a -> m a
return ((:>) (RL p) (RL p) wX wY -> m ((:>) (RL p) (RL p) wX wY))
-> (:>) (RL p) (RL p) wX wY -> m ((:>) (RL p) (RL p) wX wY)
forall a b. (a -> b) -> a -> b
$ (forall wU wV. p wU wV -> Bool)
-> RL p wX wY -> (:>) (RL p) (RL p) wX wY
forall (p :: * -> * -> *) wX wY.
Commute p =>
(forall wU wV. p wU wV -> Bool)
-> RL p wX wY -> (:>) (RL p) (RL p) wX wY
partitionRL forall wU wV. p wU wV -> Bool
forall (prim :: * -> * -> *) wX wY.
PrimClassify prim =>
prim wX wY -> Bool
primIsHunk (RL p wX wY -> (:>) (RL p) (RL p) wX wY)
-> RL p wX wY -> (:>) (RL p) (RL p) wX wY
forall a b. (a -> b) -> a -> b
$ FL p wX wY -> RL p wX wY
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> RL a wX wZ
reverseFL FL p wX wY
ps
FL p wX wZ -> Tree m -> m (Tree m)
forall (p :: * -> * -> *) (m :: * -> *) wX wY.
(Apply p, Monad m, ApplyState p ~ Tree) =>
p wX wY -> Tree m -> m (Tree m)
applyToTree (RL p wX wZ -> FL p wX wZ
forall (a :: * -> * -> *) wX wZ. RL a wX wZ -> FL a wX wZ
reverseRL RL p wX wZ
adds) Tree m
pristine
exitOnNoChanges :: FL p wX wY -> IO ()
exitOnNoChanges :: FL p wX wY -> IO ()
exitOnNoChanges FL p wX wY
NilFL = do String -> IO ()
putStrLn String
"No changes!"
ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith (ExitCode -> IO ()) -> ExitCode -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> ExitCode
ExitFailure Int
1
exitOnNoChanges FL p wX wY
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
samePatchType :: FL p wX wY -> FL p wU wV -> IO ()
samePatchType :: FL p wX wY -> FL p wU wV -> IO ()
samePatchType FL p wX wY
_ FL p wU wV
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
printUnaddedPaths :: PrimPatch p => FL p wX wY -> IO ()
printUnaddedPaths :: FL p wX wY -> IO ()
printUnaddedPaths FL p wX wY
NilFL = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
printUnaddedPaths FL p wX wY
ps =
Doc -> IO ()
putDocLn (Doc -> IO ()) -> (FL p wX wY -> Doc) -> FL p wX wY -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Doc
lowercaseAs (String -> Doc) -> (FL p wX wY -> String) -> FL p wX wY -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> String
renderString (Doc -> String) -> (FL p wX wY -> Doc) -> FL p wX wY -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> FL p wX wY -> Doc
forall (prim :: * -> * -> *) wX wY.
PrimDetails prim =>
Bool -> FL prim wX wY -> Doc
plainSummaryPrims Bool
False) (FL p wX wY -> IO ()) -> FL p wX wY -> IO ()
forall a b. (a -> b) -> a -> b
$ FL p wX wY
ps
lowercaseAs :: String -> Doc
lowercaseAs String
x = [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Doc
text (String -> Doc) -> (String -> String) -> String -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
lowercaseA) ([String] -> [Doc]) -> [String] -> [Doc]
forall a b. (a -> b) -> a -> b
$ String -> [String]
lines String
x
lowercaseA :: String -> String
lowercaseA (Char
'A' : String
x) = Char
'a' Char -> String -> String
forall a. a -> [a] -> [a]
: String
x
lowercaseA String
x = String
x
printChanges :: ( PrimPatch p, ApplyState p ~ Tree)
=> Tree IO -> FL p wX wY
-> IO ()
printChanges :: Tree IO -> FL p wX wY -> IO ()
printChanges Tree IO
pristine FL p wX wY
changes
| Bool
haveSummary = Doc -> IO ()
putDocLn (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> FL p wX wY -> Doc
forall (prim :: * -> * -> *) wX wY.
PrimDetails prim =>
Bool -> FL prim wX wY -> Doc
plainSummaryPrims Bool
machineReadable FL p wX wY
changes
| WithContext -> Bool
forall a. YesNo a => a -> Bool
O.yes (PrimDarcsOption WithContext
withContext PrimDarcsOption WithContext -> [Flag] -> WithContext
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [Flag]
opts) = Tree IO -> FL p wX wY -> IO ()
forall (p :: * -> * -> *) wX wY.
(ShowContextPatch p, ApplyState p ~ Tree) =>
Tree IO -> p wX wY -> IO ()
contextualPrintPatch Tree IO
pristine FL p wX wY
changes
| Bool
otherwise = FL p wX wY -> IO ()
forall (p :: * -> * -> *) wX wY.
ShowPatchBasic p =>
p wX wY -> IO ()
printPatchPager FL p wX wY
changes
where machineReadable :: Bool
machineReadable = PrimDarcsOption Bool -> [Flag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
parseFlags PrimDarcsOption Bool
O.machineReadable [Flag]
opts
filteredUnrecordedChanges :: forall rt p wR wU. (RepoPatch p, ApplyState p ~ Tree)
=> (O.UseIndex, O.ScanKnown, O.DiffAlgorithm)
-> O.LookForMoves
-> O.LookForReplaces
-> Repository rt p wR wU wR
-> Maybe [AnchoredPath]
-> IO (Sealed (FL (PrimOf p) wR))
filteredUnrecordedChanges :: (UseIndex, ScanKnown, DiffAlgorithm)
-> LookForMoves
-> LookForReplaces
-> Repository rt p wR wU wR
-> Maybe [AnchoredPath]
-> IO (Sealed (FL (PrimOf p) wR))
filteredUnrecordedChanges (UseIndex, ScanKnown, DiffAlgorithm)
diffing LookForMoves
lfm LookForReplaces
lfr Repository rt p wR wU wR
repo Maybe [AnchoredPath]
paths =
Maybe [AnchoredPath]
-> FL (PrimOf p) wR wU -> Sealed (FL (PrimOf p) wR)
forall (p :: * -> * -> *) wX wY.
(Apply p, Commute p, PatchInspect p, ApplyState p ~ Tree) =>
Maybe [AnchoredPath] -> FL p wX wY -> Sealed (FL p wX)
chooseTouching Maybe [AnchoredPath]
paths (FL (PrimOf p) wR wU -> Sealed (FL (PrimOf p) wR))
-> IO (FL (PrimOf p) wR wU) -> IO (Sealed (FL (PrimOf p) wR))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (UseIndex, ScanKnown, DiffAlgorithm)
-> LookForMoves
-> LookForReplaces
-> Repository rt p wR wU wR
-> Maybe [AnchoredPath]
-> IO (FL (PrimOf p) wR wU)
forall (p :: * -> * -> *) (rt :: RepoType) wR wU.
(RepoPatch p, ApplyState p ~ Tree) =>
(UseIndex, ScanKnown, DiffAlgorithm)
-> LookForMoves
-> LookForReplaces
-> Repository rt p wR wU wR
-> Maybe [AnchoredPath]
-> IO (FL (PrimOf p) wR wU)
unrecordedChanges (UseIndex, ScanKnown, DiffAlgorithm)
diffing LookForMoves
lfm LookForReplaces
lfr Repository rt p wR wU wR
repo Maybe [AnchoredPath]
paths
runInteractive :: InteractiveSelectionM p wX wY ()
-> S.PatchSelectionOptions
-> Tree IO
-> FL p wX wY
-> IO ()
runInteractive :: InteractiveSelectionM p wX wY ()
-> PatchSelectionOptions -> Tree IO -> FL p wX wY -> IO ()
runInteractive InteractiveSelectionM p wX wY ()
i PatchSelectionOptions
patchsel Tree IO
pristine FL p wX wY
ps' = do
let lps' :: FL (LabelledPatch p) wX wY
lps' = Maybe Label -> FL p wX wY -> FL (LabelledPatch p) wX wY
forall (p :: * -> * -> *) wX wY.
Maybe Label -> FL p wX wY -> FL (LabelledPatch p) wX wY
labelPatches Maybe Label
forall a. Maybe a
Nothing FL p wX wY
ps'
choices' :: PatchChoices p wX wY
choices' = FL (LabelledPatch p) wX wY -> PatchChoices p wX wY
forall (p :: * -> * -> *) wX wY.
FL (LabelledPatch p) wX wY -> PatchChoices p wX wY
mkPatchChoices FL (LabelledPatch p) wX wY
lps'
ps :: PatchSelectionM p IO ()
ps = InteractiveSelectionM p wX wY ()
-> InteractiveSelectionState p wX wY -> PatchSelectionM p IO ()
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT InteractiveSelectionM p wX wY ()
i (FL (LabelledPatch p) wX wY
-> PatchChoices p wX wY -> InteractiveSelectionState p wX wY
forall (p :: * -> * -> *) wX wY.
FL (LabelledPatch p) wX wY
-> PatchChoices p wX wY -> InteractiveSelectionState p wX wY
initialSelectionState FL (LabelledPatch p) wX wY
lps' PatchChoices p wX wY
choices')
IO () -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
PatchSelectionM p IO () -> SelectionConfig p -> IO ()
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT PatchSelectionM p IO ()
ps (SelectionConfig p -> IO ()) -> SelectionConfig p -> IO ()
forall a b. (a -> b) -> a -> b
$
WhichChanges
-> String
-> PatchSelectionOptions
-> Maybe (Splitter p)
-> Maybe [AnchoredPath]
-> Maybe (Tree IO)
-> SelectionConfig p
forall (prim :: * -> * -> *).
WhichChanges
-> String
-> PatchSelectionOptions
-> Maybe (Splitter prim)
-> Maybe [AnchoredPath]
-> Maybe (Tree IO)
-> SelectionConfig prim
selectionConfigPrim WhichChanges
First String
"view" PatchSelectionOptions
patchsel Maybe (Splitter p)
forall a. Maybe a
Nothing Maybe [AnchoredPath]
forall a. Maybe a
Nothing (Tree IO -> Maybe (Tree IO)
forall a. a -> Maybe a
Just Tree IO
pristine)
interactiveHunks :: (IsHunk p, ShowPatch p, ShowContextPatch p, Commute p,
PatchInspect p, PrimDetails p, ApplyState p ~ Tree)
=> Tree IO -> InteractiveSelectionM p wX wY ()
interactiveHunks :: Tree IO -> InteractiveSelectionM p wX wY ()
interactiveHunks Tree IO
pristine = do
Maybe (Sealed2 (LabelledPatch p))
c <- InteractiveSelectionM p wX wY (Maybe (Sealed2 (LabelledPatch p)))
forall (p :: * -> * -> *) wX wY.
InteractiveSelectionM p wX wY (Maybe (Sealed2 (LabelledPatch p)))
currentPatch
case Maybe (Sealed2 (LabelledPatch p))
c of
Maybe (Sealed2 (LabelledPatch p))
Nothing -> IO () -> InteractiveSelectionM p wX wY ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> InteractiveSelectionM p wX wY ())
-> IO () -> InteractiveSelectionM p wX wY ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
putStrLn String
"No more changes!"
Just (Sealed2 LabelledPatch p wX wY
lp) -> do
IO () -> InteractiveSelectionM p wX wY ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> InteractiveSelectionM p wX wY ())
-> IO () -> InteractiveSelectionM p wX wY ()
forall a b. (a -> b) -> a -> b
$ p wX wY -> IO ()
forall (p :: * -> * -> *) wX wY.
ShowPatchBasic p =>
p wX wY -> IO ()
printPatchPager (LabelledPatch p wX wY -> p wX wY
forall (p :: * -> * -> *) wX wY. LabelledPatch p wX wY -> p wX wY
unLabel LabelledPatch p wX wY
lp)
LabelledPatch p wX wY -> InteractiveSelectionM p wX wY ()
forall wX wY wX wY.
LabelledPatch p wX wY
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
repeatThis LabelledPatch p wX wY
lp
where
repeatThis :: LabelledPatch p wX wY
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
repeatThis LabelledPatch p wX wY
lp = do
String
thePrompt <- InteractiveSelectionM p wX wY String
forall (p :: * -> * -> *) wX wY.
ShowPatch p =>
InteractiveSelectionM p wX wY String
prompt
Char
yorn <- IO Char
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) Char
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Char
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) Char)
-> IO Char
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) Char
forall a b. (a -> b) -> a -> b
$ PromptConfig -> IO Char
promptChar
(String -> String -> String -> Maybe Char -> String -> PromptConfig
PromptConfig String
thePrompt ([[KeyPress]] -> String
keysFor [[KeyPress]]
basic_options) ([[KeyPress]] -> String
keysFor [[KeyPress]]
adv_options)
(Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'n') String
"?h")
case Char
yorn of
Char
'v' -> IO ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Tree IO -> p wX wY -> IO ()
forall (p :: * -> * -> *) wX wY.
(ShowContextPatch p, ApplyState p ~ Tree) =>
Tree IO -> p wX wY -> IO ()
contextualPrintPatch Tree IO
pristine (LabelledPatch p wX wY -> p wX wY
forall (p :: * -> * -> *) wX wY. LabelledPatch p wX wY -> p wX wY
unLabel LabelledPatch p wX wY
lp))
StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LabelledPatch p wX wY
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
repeatThis LabelledPatch p wX wY
lp
Char
'x' -> IO ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Doc -> IO ()
putDocLn (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ p wX wY -> Doc
forall (p :: * -> * -> *) wX wY. ShowPatch p => p wX wY -> Doc
summary (p wX wY -> Doc) -> p wX wY -> Doc
forall a b. (a -> b) -> a -> b
$ LabelledPatch p wX wY -> p wX wY
forall (p :: * -> * -> *) wX wY. LabelledPatch p wX wY -> p wX wY
unLabel LabelledPatch p wX wY
lp)
StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LabelledPatch p wX wY
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
repeatThis LabelledPatch p wX wY
lp
Char
'y' -> IO ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Tree IO -> p wX wY -> IO ()
forall (p :: * -> * -> *) wX wY.
(ShowContextPatch p, ApplyState p ~ Tree) =>
Tree IO -> p wX wY -> IO ()
contextualPrintPatch Tree IO
pristine (LabelledPatch p wX wY -> p wX wY
forall (p :: * -> * -> *) wX wY. LabelledPatch p wX wY -> p wX wY
unLabel LabelledPatch p wX wY
lp))
StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool
-> LabelledPatch p wX wY
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (p :: * -> * -> *) wT wU wX wY.
Commute p =>
Bool -> LabelledPatch p wT wU -> InteractiveSelectionM p wX wY ()
decide Bool
True LabelledPatch p wX wY
lp StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall wX wY.
StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
next_hunk
Char
'n' -> Bool
-> LabelledPatch p wX wY
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (p :: * -> * -> *) wT wU wX wY.
Commute p =>
Bool -> LabelledPatch p wT wU -> InteractiveSelectionM p wX wY ()
decide Bool
False LabelledPatch p wX wY
lp StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall wX wY.
StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
next_hunk
Char
's' -> do
InteractiveSelectionM p wX wY (Maybe AnchoredPath)
forall (p :: * -> * -> *) wX wY.
PatchInspect p =>
InteractiveSelectionM p wX wY (Maybe AnchoredPath)
currentFile InteractiveSelectionM p wX wY (Maybe AnchoredPath)
-> (Maybe AnchoredPath
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ())
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> (AnchoredPath
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ())
-> Maybe AnchoredPath
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
(\AnchoredPath
f -> AnchoredPath
-> Bool
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (p :: * -> * -> *) wX wY.
(Commute p, PatchInspect p) =>
AnchoredPath -> Bool -> InteractiveSelectionM p wX wY ()
decideWholeFile AnchoredPath
f Bool
False)
StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall wX wY.
StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
next_hunk
Char
'p' -> IO ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (p wX wY -> IO ()
forall (p :: * -> * -> *) wX wY.
ShowPatchBasic p =>
p wX wY -> IO ()
printPatchPager (p wX wY -> IO ()) -> p wX wY -> IO ()
forall a b. (a -> b) -> a -> b
$ LabelledPatch p wX wY -> p wX wY
forall (p :: * -> * -> *) wX wY. LabelledPatch p wX wY -> p wX wY
unLabel LabelledPatch p wX wY
lp)
StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LabelledPatch p wX wY
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
repeatThis LabelledPatch p wX wY
lp
Char
'j' -> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall wX wY.
StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
next_hunk
Char
'k' -> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall wX wY.
StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
prev_hunk
Char
'g' -> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall wX wY.
StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
start_over
Char
'q' -> IO ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ())
-> IO ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall a b. (a -> b) -> a -> b
$ IO ()
forall a. IO a
exitSuccess
Char
_ -> do IO ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ())
-> (String -> IO ())
-> String
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ()
putStrLn (String
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ())
-> String
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall a b. (a -> b) -> a -> b
$
String -> [[KeyPress]] -> [[KeyPress]] -> String
helpFor String
"whatsnew" [[KeyPress]]
basic_options [[KeyPress]]
adv_options
LabelledPatch p wX wY
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
repeatThis LabelledPatch p wX wY
lp
start_over :: StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
start_over = StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (p :: * -> * -> *) wX wY. InteractiveSelectionM p wX wY ()
backAll StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Tree IO
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (p :: * -> * -> *) wX wY.
(IsHunk p, ShowPatch p, ShowContextPatch p, Commute p,
PatchInspect p, PrimDetails p, ApplyState p ~ Tree) =>
Tree IO -> InteractiveSelectionM p wX wY ()
interactiveHunks Tree IO
pristine
next_hunk :: StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
next_hunk = StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (p :: * -> * -> *) wX wY. InteractiveSelectionM p wX wY ()
skipOne StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (p :: * -> * -> *) wX wY.
(Commute p, ShowPatch p) =>
InteractiveSelectionM p wX wY ()
skipMundane StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Tree IO
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (p :: * -> * -> *) wX wY.
(IsHunk p, ShowPatch p, ShowContextPatch p, Commute p,
PatchInspect p, PrimDetails p, ApplyState p ~ Tree) =>
Tree IO -> InteractiveSelectionM p wX wY ()
interactiveHunks Tree IO
pristine
prev_hunk :: StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
prev_hunk = StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (p :: * -> * -> *) wX wY. InteractiveSelectionM p wX wY ()
backOne StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Tree IO
-> StateT
(InteractiveSelectionState p wX wY) (PatchSelectionM p IO) ()
forall (p :: * -> * -> *) wX wY.
(IsHunk p, ShowPatch p, ShowContextPatch p, Commute p,
PatchInspect p, PrimDetails p, ApplyState p ~ Tree) =>
Tree IO -> InteractiveSelectionM p wX wY ()
interactiveHunks Tree IO
pristine
options_yn :: [KeyPress]
options_yn =
[ Char -> String -> KeyPress
KeyPress Char
'v' String
"view this change in a context"
, Char -> String -> KeyPress
KeyPress Char
'y' String
"view this change in a context and go to the next one"
, Char -> String -> KeyPress
KeyPress Char
'n' String
"skip this change and its dependencies" ]
optionsView :: [KeyPress]
optionsView =
[ Char -> String -> KeyPress
KeyPress Char
'p' String
"view this change in context wih pager "
, Char -> String -> KeyPress
KeyPress Char
'x' String
"view a summary of this change"
]
optionsNav :: [KeyPress]
optionsNav =
[ Char -> String -> KeyPress
KeyPress Char
'q' String
"quit whatsnew"
, Char -> String -> KeyPress
KeyPress Char
's' String
"skip the rest of the changes to this file"
, Char -> String -> KeyPress
KeyPress Char
'j' String
"go to the next change"
, Char -> String -> KeyPress
KeyPress Char
'k' String
"back up to previous change"
, Char -> String -> KeyPress
KeyPress Char
'g' String
"start over from the first change"
]
basic_options :: [[KeyPress]]
basic_options = [ [KeyPress]
options_yn ]
adv_options :: [[KeyPress]]
adv_options = [ [KeyPress]
optionsView, [KeyPress]
optionsNav ]
printPatchPager :: ShowPatchBasic p => p wX wY -> IO ()
= Printers -> Doc -> IO ()
viewDocWith Printers
fancyPrinters (Doc -> IO ()) -> (p wX wY -> Doc) -> p wX wY -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p wX wY -> Doc
forall (p :: * -> * -> *) wX wY. ShowPatchBasic p => p wX wY -> Doc
displayPatch
status :: DarcsCommand
status :: DarcsCommand
status = DarcsCommand
statusAlias
{ commandDescription :: String
commandDescription = String
statusDesc
, commandAdvancedOptions :: [DarcsOptDescr Flag]
commandAdvancedOptions = OptSpec DarcsOptDescr Flag Any (UseIndex -> IncludeBoring -> Any)
-> [DarcsOptDescr Flag]
forall (d :: * -> *) f a b. OptSpec d f a b -> [d f]
odesc OptSpec DarcsOptDescr Flag Any (UseIndex -> IncludeBoring -> Any)
forall a. DarcsOption a (UseIndex -> IncludeBoring -> a)
commonAdvancedOpts
, commandBasicOptions :: [DarcsOptDescr Flag]
commandBasicOptions = OptSpec
DarcsOptDescr
Flag
Any
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Any)
-> [DarcsOptDescr Flag]
forall (d :: * -> *) f a b. OptSpec d f a b -> [d f]
odesc OptSpec
DarcsOptDescr
Flag
Any
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Any)
forall a.
OptSpec
DarcsOptDescr
Flag
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
statusBasicOpts
, commandDefaults :: [Flag]
commandDefaults = OptSpec
DarcsOptDescr
Flag
[Flag]
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> [Flag])
-> [Flag]
forall (d :: * -> *) f b. OptSpec d f [f] b -> [f]
defaultFlags OptSpec
DarcsOptDescr
Flag
[Flag]
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> [Flag])
forall a.
DarcsOption
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
statusOpts
, commandCheckOptions :: [Flag] -> [String]
commandCheckOptions = OptSpec
DarcsOptDescr
Flag
Any
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> Any)
-> [Flag] -> [String]
forall (d :: * -> *) f a b. OptSpec d f a b -> [f] -> [String]
ocheck OptSpec
DarcsOptDescr
Flag
Any
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> Any)
forall a.
DarcsOption
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
statusOpts
}
where
statusAlias :: DarcsCommand
statusAlias = String -> Maybe DarcsCommand -> DarcsCommand -> DarcsCommand
commandAlias String
"status" Maybe DarcsCommand
forall a. Maybe a
Nothing DarcsCommand
whatsnew
statusDesc :: String
statusDesc = String
"Alias for `darcs " String -> String -> String
forall a. [a] -> [a] -> [a]
++ DarcsCommand -> String
commandName DarcsCommand
whatsnew String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" -ls`."
statusBasicOpts :: OptSpec
DarcsOptDescr
Flag
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
statusBasicOpts
= Maybe WithSummary
-> forall a. PrimOptSpec DarcsOptDescr Flag a (Maybe WithSummary)
O.maybeSummary (WithSummary -> Maybe WithSummary
forall a. a -> Maybe a
Just WithSummary
O.YesSummary)
PrimOptSpec
DarcsOptDescr
Flag
(WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
(Maybe WithSummary)
-> OptSpec
DarcsOptDescr
Flag
(Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
(WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
Flag
(Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
(WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
PrimDarcsOption WithContext
O.withContext
OptSpec
DarcsOptDescr
Flag
(Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
(Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
Flag
(LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
(Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
PrimDarcsOption Bool
O.machineReadable
OptSpec
DarcsOptDescr
Flag
(LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
(LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ LookForAdds -> PrimDarcsOption LookForAdds
O.lookforadds LookForAdds
O.YesLookForAdds
OptSpec
DarcsOptDescr
Flag
(LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(LookForMoves -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(LookForMoves -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
Flag
(LookForMoves -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
PrimDarcsOption LookForReplaces
O.lookforreplaces
OptSpec
DarcsOptDescr
Flag
(LookForMoves -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(LookForMoves -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
Flag
(DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
Flag
(DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(LookForMoves -> DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
PrimDarcsOption LookForMoves
O.lookformoves
OptSpec
DarcsOptDescr
Flag
(DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe String -> Maybe Bool -> a)
(DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
Flag
(Maybe String -> Maybe Bool -> a)
(DiffAlgorithm -> Maybe String -> Maybe Bool -> a)
PrimDarcsOption DiffAlgorithm
O.diffAlgorithm
OptSpec
DarcsOptDescr
Flag
(Maybe String -> Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe Bool -> a)
(Maybe String -> Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
Flag
(Maybe Bool -> a)
(Maybe String -> Maybe Bool -> a)
PrimDarcsOption (Maybe String)
O.repoDir
OptSpec
DarcsOptDescr
Flag
(Maybe Bool -> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec DarcsOptDescr Flag a (Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
Flag
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec DarcsOptDescr Flag a (Maybe Bool -> a)
PrimDarcsOption (Maybe Bool)
O.interactive
statusOpts :: DarcsOption
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
statusOpts = OptSpec
DarcsOptDescr
Flag
(Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
forall a.
OptSpec
DarcsOptDescr
Flag
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> a)
statusBasicOpts OptSpec
DarcsOptDescr
Flag
(Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
-> DarcsOption
(UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
(UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
-> DarcsOption
a
(Maybe WithSummary
-> WithContext
-> Bool
-> LookForAdds
-> LookForReplaces
-> LookForMoves
-> DiffAlgorithm
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
forall b c a.
DarcsOption (Maybe StdCmdAction -> Verbosity -> b) c
-> DarcsOption
(UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a) b
-> DarcsOption a c
`withStdOpts` DarcsOption
(UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
(UseIndex
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
forall a. DarcsOption a (UseIndex -> IncludeBoring -> a)
commonAdvancedOpts
maybeIsInteractive :: [DarcsFlag] -> Bool
maybeIsInteractive :: [Flag] -> Bool
maybeIsInteractive = Bool -> (Bool -> Bool) -> Maybe Bool -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False Bool -> Bool
forall a. a -> a
id (Maybe Bool -> Bool) -> ([Flag] -> Maybe Bool) -> [Flag] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PrimDarcsOption (Maybe Bool) -> [Flag] -> Maybe Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
parseFlags PrimDarcsOption (Maybe Bool)
O.interactive