{-# 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 = O.useIndex ^ O.includeBoring
patchSelOpts :: [DarcsFlag] -> S.PatchSelectionOptions
patchSelOpts flags = S.PatchSelectionOptions
{ S.verbosity = verbosity ? flags
, S.matchFlags = []
, S.interactive = isInteractive True flags
, S.selectDeps = O.PromptDeps
, S.withSummary = getSummary flags
, S.withContext = withContext ? flags
}
getSummary :: [DarcsFlag] -> O.WithSummary
getSummary flags = case O.maybeSummary Nothing ? flags of
Just O.NoSummary -> O.NoSummary
Just O.YesSummary -> O.YesSummary
Nothing
| O.yes (lookForAdds flags) -> O.YesSummary
| O.machineReadable ? flags -> O.YesSummary
| otherwise -> O.NoSummary
whatsnew :: DarcsCommand
whatsnew = DarcsCommand
{ commandProgramName = "darcs"
, commandName = "whatsnew"
, commandHelp = whatsnewHelp
, commandDescription = whatsnewDescription
, commandExtraArgs = -1
, commandExtraArgHelp = ["[FILE or DIRECTORY]..."]
, commandCommand = whatsnewCmd
, commandPrereq = amInRepository
, commandCompleteArgs = modifiedFileArgs
, commandArgdefaults = nodefaults
, commandAdvancedOptions = odesc commonAdvancedOpts
, commandBasicOptions = odesc whatsnewBasicOpts
, commandDefaults = defaultFlags whatsnewOpts
, commandCheckOptions = ocheck whatsnewOpts
}
where
whatsnewBasicOpts
= O.maybeSummary Nothing
^ O.withContext
^ O.machineReadable
^ O.lookfor
^ O.diffAlgorithm
^ O.repoDir
^ O.interactive
whatsnewOpts = whatsnewBasicOpts `withStdOpts` commonAdvancedOpts
whatsnewDescription :: String
whatsnewDescription = "List unrecorded changes in the working tree."
whatsnewHelp :: Doc
whatsnewHelp =
formatWords
[ "The `darcs whatsnew` command lists unrecorded changes to the working"
, "tree. If you specify a set of files and directories, only unrecorded"
, "changes to those files and directories are listed."
]
$+$ formatWords
[ "With the `--summary` option, the changes are condensed to one line per"
, "file, with mnemonics to indicate the nature and extent of the change."
, "The `--look-for-adds` option causes candidates for `darcs add` to be"
, "included in the summary output. WithSummary mnemonics are as follows:"
]
$+$ vcat
[ " * `A f` and `A d/` respectively mean an added file or directory."
, " * `R f` and `R d/` respectively mean a removed file or directory."
, " * `M f -N +M rP` means a modified file, with `N` lines deleted, `M`"
, " lines added, and `P` lexical replacements."
, " * `f -> g` means a moved file or directory."
, " * `a f` and `a d/` respectively mean a new, but unadded, file or"
, " directory, when using `--look-for-adds`."
, " * An exclamation mark (!) as in `R! foo.c`, means the change"
, " conflicts with a change in an earlier patch. The phrase `duplicated`"
, " means the change is identical to a change in an earlier patch."
]
$+$ formatWords
[ "The `--machine-readable` option implies `--summary` while making it more"
, "parsable. Modified files are only shown as `M f`, and moves are shown in"
, "two lines: `F f` and `T g` (as in 'From f To g')."
]
$+$ formatWords
[ "By default, `darcs whatsnew` uses Darcs' internal format for changes."
, "To see some context (unchanged lines) around each change, use the"
, "`--unified` option. To view changes in conventional `diff` format, use"
, "the `darcs diff` command; but note that `darcs whatsnew` is faster."
]
$+$ formatWords
[ "This command exits unsuccessfully (returns a non-zero exit status) if"
, "there are no unrecorded changes."
]
whatsnewCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
whatsnewCmd fps opts args =
withRepository (useCache ? opts) $ RepoJob $ \(repo :: Repository rt p wR wU wR) -> do
let scan = scanKnown (lookForAdds opts) (O.includeBoring ? opts)
existing_files <- do
files <- pathSetFromArgs fps args
files' <- traverse
(filterExistingPaths
repo (verbosity ? opts) (useIndex ? opts) scan (lookForMoves opts))
files
let files'' = fmap snd files'
when (files'' == Just []) $
fail "None of the files you specified exist."
return files''
Sealed allInterestingChanges <-
filteredUnrecordedChanges (diffingOpts opts)
(lookForMoves opts) (lookForReplaces opts)
repo existing_files
pristine <- readRecorded repo
Sealed noLookChanges <-
if haveLookForAddsAndSummary
then
filteredUnrecordedChanges (O.useIndex ? opts, O.ScanKnown, O.diffAlgorithm ? opts)
(lookForMoves opts) (lookForReplaces opts)
repo existing_files
else return (Sealed NilFL)
Sealed unaddedNewPathsPs <-
if haveLookForAddsAndSummary
then do
noLookAddsTree <- applyAddPatchesToPristine noLookChanges pristine
lookAddsTree <- applyAddPatchesToPristine allInterestingChanges pristine
ftf <- filetypeFunction
unFreeLeft <$> treeDiff (diffAlgorithm ? opts) ftf noLookAddsTree lookAddsTree
else return (Sealed NilFL)
samePatchType noLookChanges unaddedNewPathsPs
exitOnNoChanges allInterestingChanges
announceFiles (verbosity ? opts) existing_files "What's new in"
if maybeIsInteractive opts
then
runInteractive (interactiveHunks pristine) (patchSelOpts opts)
pristine allInterestingChanges
else
if haveLookForAddsAndSummary
then do
printChanges pristine noLookChanges
printUnaddedPaths unaddedNewPathsPs
else do
printChanges pristine allInterestingChanges
where
haveSummary = O.yes (getSummary opts)
haveLookForAddsAndSummary = haveSummary && O.yes (lookForAdds opts)
applyAddPatchesToPristine ps pristine = do
adds :> _ <- return $ partitionRL primIsHunk $ reverseFL ps
applyToTree (reverseRL adds) pristine
exitOnNoChanges :: FL p wX wY -> IO ()
exitOnNoChanges NilFL = do putStrLn "No changes!"
exitWith $ ExitFailure 1
exitOnNoChanges _ = return ()
samePatchType :: FL p wX wY -> FL p wU wV -> IO ()
samePatchType _ _ = return ()
printUnaddedPaths :: PrimPatch p => FL p wX wY -> IO ()
printUnaddedPaths NilFL = return ()
printUnaddedPaths ps =
putDocLn . lowercaseAs . renderString . (plainSummaryPrims False) $ ps
lowercaseAs x = vcat $ map (text . lowercaseA) $ lines x
lowercaseA ('A' : x) = 'a' : x
lowercaseA x = x
printChanges :: ( PrimPatch p, ApplyState p ~ Tree)
=> Tree IO -> FL p wX wY
-> IO ()
printChanges pristine changes
| haveSummary = putDocLn $ plainSummaryPrims machineReadable changes
| O.yes (withContext ? opts) = contextualPrintPatch pristine changes
| otherwise = printPatchPager changes
where machineReadable = parseFlags O.machineReadable 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 diffing lfm lfr repo paths =
chooseTouching paths <$> unrecordedChanges diffing lfm lfr repo paths
runInteractive :: InteractiveSelectionM p wX wY ()
-> S.PatchSelectionOptions
-> Tree IO
-> FL p wX wY
-> IO ()
runInteractive i patchsel pristine ps' = do
let lps' = labelPatches Nothing ps'
choices' = mkPatchChoices lps'
ps = evalStateT i (initialSelectionState lps' choices')
void $
runReaderT ps $
selectionConfigPrim First "view" patchsel Nothing Nothing (Just pristine)
interactiveHunks :: (IsHunk p, ShowPatch p, ShowContextPatch p, Commute p,
PatchInspect p, PrimDetails p, ApplyState p ~ Tree)
=> Tree IO -> InteractiveSelectionM p wX wY ()
interactiveHunks pristine = do
c <- currentPatch
case c of
Nothing -> liftIO $ putStrLn "No more changes!"
Just (Sealed2 lp) -> do
liftIO $ printPatchPager (unLabel lp)
repeatThis lp
where
repeatThis lp = do
thePrompt <- prompt
yorn <- liftIO $ promptChar
(PromptConfig thePrompt (keysFor basic_options) (keysFor adv_options)
(Just 'n') "?h")
case yorn of
'v' -> liftIO (contextualPrintPatch pristine (unLabel lp))
>> repeatThis lp
'x' -> liftIO (putDocLn $ summary $ unLabel lp)
>> repeatThis lp
'y' -> liftIO (contextualPrintPatch pristine (unLabel lp))
>> decide True lp >> next_hunk
'n' -> decide False lp >> next_hunk
's' -> do
currentFile >>= maybe
(return ())
(\f -> decideWholeFile f False)
next_hunk
'p' -> liftIO (printPatchPager $ unLabel lp)
>> repeatThis lp
'j' -> next_hunk
'k' -> prev_hunk
'g' -> start_over
'q' -> liftIO $ exitSuccess
_ -> do liftIO . putStrLn $
helpFor "whatsnew" basic_options adv_options
repeatThis lp
start_over = backAll >> interactiveHunks pristine
next_hunk = skipOne >> skipMundane >> interactiveHunks pristine
prev_hunk = backOne >> interactiveHunks pristine
options_yn =
[ KeyPress 'v' "view this change in a context"
, KeyPress 'y' "view this change in a context and go to the next one"
, KeyPress 'n' "skip this change and its dependencies" ]
optionsView =
[ KeyPress 'p' "view this change in context wih pager "
, KeyPress 'x' "view a summary of this change"
]
optionsNav =
[ KeyPress 'q' "quit whatsnew"
, KeyPress 's' "skip the rest of the changes to this file"
, KeyPress 'j' "go to the next change"
, KeyPress 'k' "back up to previous change"
, KeyPress 'g' "start over from the first change"
]
basic_options = [ options_yn ]
adv_options = [ optionsView, optionsNav ]
printPatchPager :: ShowPatchBasic p => p wX wY -> IO ()
printPatchPager = viewDocWith fancyPrinters . displayPatch
status :: DarcsCommand
status = statusAlias
{ commandDescription = statusDesc
, commandAdvancedOptions = odesc commonAdvancedOpts
, commandBasicOptions = odesc statusBasicOpts
, commandDefaults = defaultFlags statusOpts
, commandCheckOptions = ocheck statusOpts
}
where
statusAlias = commandAlias "status" Nothing whatsnew
statusDesc = "Alias for `darcs " ++ commandName whatsnew ++ " -ls`."
statusBasicOpts
= O.maybeSummary (Just O.YesSummary)
^ O.withContext
^ O.machineReadable
^ O.lookforadds O.YesLookForAdds
^ O.lookforreplaces
^ O.lookformoves
^ O.diffAlgorithm
^ O.repoDir
^ O.interactive
statusOpts = statusBasicOpts `withStdOpts` commonAdvancedOpts
maybeIsInteractive :: [DarcsFlag] -> Bool
maybeIsInteractive = maybe False id . parseFlags O.interactive