{-# LANGUAGE OverloadedStrings #-}
module Darcs.UI.Commands.Record
( record
, commit
) where
import Darcs.Prelude
import Data.Foldable ( traverse_ )
import Control.Exception ( handleJust )
import Control.Monad ( when, unless, void )
import Data.Char ( ord )
import System.Exit ( exitFailure, exitSuccess, ExitCode(..) )
import System.Directory ( removeFile )
import Darcs.Patch.PatchInfoAnd ( n2pia )
import Darcs.Repository
( Repository
, withRepoLock
, RepoJob(..)
, tentativelyAddPatch
, finalizeRepositoryChanges
, invalidateIndex
, readPendingAndWorking
, readRecorded
)
import Darcs.Repository.Pending ( tentativelyRemoveFromPW )
import Darcs.Patch ( IsRepoType, RepoPatch, PrimOf, sortCoalesceFL )
import Darcs.Patch.Named ( infopatch, adddeps )
import Darcs.Patch.Witnesses.Ordered
( FL(..), (:>)(..), nullFL, (+>+) )
import Darcs.Patch.Info ( PatchInfo, patchinfo )
import Darcs.Patch.Apply( ApplyState )
import Darcs.Patch.Split ( primSplitter )
import Darcs.UI.SelectChanges
( WhichChanges(..)
, selectionConfigPrim
, runInvertibleSelection
, askAboutDepends
)
import qualified Darcs.UI.SelectChanges as S ( PatchSelectionOptions(..) )
import Darcs.Util.Path ( AnchoredPath, displayPath, AbsolutePath )
import Darcs.UI.Commands
( DarcsCommand(..), withStdOpts
, nodefaults
, commandAlias
, setEnvDarcsFiles
, setEnvDarcsPatches
, amInHashedRepository
)
import Darcs.UI.Commands.Util ( announceFiles, filterExistingPaths,
testTentativeAndMaybeExit )
import Darcs.UI.Completion ( modifiedFileArgs )
import Darcs.UI.Flags
( DarcsFlag
, fileHelpAuthor
, getAuthor
, getDate
, diffOpts
, scanKnown
, pathSetFromArgs
)
import Darcs.UI.Options ( DarcsOption, (^), odesc, ocheck, oparse, defaultFlags )
import Darcs.UI.PatchHeader ( getLog )
import qualified Darcs.UI.Options.All as O
import Darcs.Repository.Flags ( UpdatePending (..), DryRun(NoDryRun), ScanKnown(..) )
import Darcs.Util.Exception ( clarifyErrors )
import Darcs.Util.Prompt ( promptYorn )
import Darcs.Util.Progress ( debugMessage )
import Darcs.Util.Global ( darcsLastMessage )
import Darcs.Patch.Progress ( progressFL )
import Darcs.Util.Printer
( Doc
, ($+$)
, (<+>)
, formatWords
, pathlist
, putDocLn
, text
, vcat
, vsep
)
import Darcs.Util.Tree( Tree )
recordHelp :: Doc
recordHelp :: Doc
recordHelp =
[Doc] -> Doc
vsep (([String] -> Doc) -> [[String]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map [String] -> Doc
formatWords
[ [ String
"The `darcs record` command is used to create a patch from changes in"
, String
"the working tree. If you specify a set of files and directories,"
, String
"changes to other files will be skipped."
]
, [ String
"Every patch has a name, an optional description, an author and a date."
]
, [ String
"Darcs will launch a text editor (see `darcs help environment`) after the"
, String
"interactive selection, to let you enter the patch name (first line) and"
, String
"the patch description (subsequent lines)."
]
, [ String
"You can supply the patch name in advance with the `-m` option, in which"
, String
"case no text editor is launched, unless you use `--edit-long-comment`."
]
, [ String
"The patch description is an optional block of free-form text. It is"
, String
"used to supply additional information that doesn't fit in the patch"
, String
"name. For example, it might include a rationale of WHY the change was"
, String
"necessary."
]
, [ String
"A technical difference between patch name and patch description, is"
, String
"that matching with the flag `-p` is only done on patch names."
]
, [ String
"Finally, the `--logfile` option allows you to supply a file that already"
, String
"contains the patch name and description. This is useful if a previous"
, String
"record failed and left a `_darcs/patch_description.txt` file."
]
, [String]
fileHelpAuthor
, [ String
"If you want to manually define any explicit dependencies for your patch,"
, String
"you can use the `--ask-deps` flag. Some dependencies may be automatically"
, String
"inferred from the patch's content and cannot be removed. A patch with"
, String
"specific dependencies can be empty."
]
, [ String
"The patch date is generated automatically. It can only be spoofed by"
, String
"using the `--pipe` option."
]
, [ String
"If you run record with the `--pipe` option, you will be prompted for"
, String
"the patch date, author, and the long comment. The long comment will extend"
, String
"until the end of file or stdin is reached. This interface is intended for"
, String
"scripting darcs, in particular for writing repository conversion scripts."
, String
"The prompts are intended mostly as a useful guide (since scripts won't"
, String
"need them), to help you understand the input format. Here's an example of"
, String
"what the `--pipe` prompts look like:"
]
])
Doc -> Doc -> Doc
$+$ [Doc] -> Doc
vcat
[ Doc
" What is the date? Mon Nov 15 13:38:01 EST 2004"
, Doc
" Who is the author? David Roundy"
, Doc
" What is the log? One or more comment lines"
]
Doc -> Doc -> Doc
$+$ [Doc] -> Doc
vsep (([String] -> Doc) -> [[String]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map [String] -> Doc
formatWords
[ [ String
"If a test command has been defined with `darcs setpref`, attempting to"
, String
"record a patch will cause the test command to be run in a clean copy"
, String
"of the working tree (that is, including only recorded changes). If"
, String
"the test fails, you will be offered to abort the record operation."
]
, [ String
"The `--set-scripts-executable` option causes scripts to be made"
, String
"executable in the clean copy of the working tree, prior to running the"
, String
"test. See `darcs clone` for an explanation of the script heuristic."
]
, [ String
"If your test command is tediously slow (e.g. `make all`) and you are"
, String
"recording several patches in a row, you may wish to use `--no-test` to"
, String
"skip all but the final test."
]
, [ String
"To see some context (unchanged lines) around each change, use the"
, String
"`--unified` option."
]
])
recordBasicOpts :: DarcsOption a
(Maybe String
-> Maybe String
-> O.TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe O.AskLongComment
-> O.LookFor
-> Maybe String
-> O.WithContext
-> O.DiffAlgorithm
-> a)
recordBasicOpts :: DarcsOption
a
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
recordBasicOpts
= PrimOptSpec
DarcsOptDescr
Flag
(Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe String)
PrimDarcsOption (Maybe String)
O.patchname
PrimOptSpec
DarcsOptDescr
Flag
(Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe String)
-> OptSpec
DarcsOptDescr
Flag
(TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
Flag
(TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> 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
(TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
PrimDarcsOption (Maybe String)
O.author
OptSpec
DarcsOptDescr
Flag
(TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> 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
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
PrimDarcsOption TestChanges
O.testChanges
OptSpec
DarcsOptDescr
Flag
(Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> 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
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
PrimDarcsOption (Maybe Bool)
O.interactive
OptSpec
DarcsOptDescr
Flag
(Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> 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
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
PrimDarcsOption Bool
O.pipe
OptSpec
DarcsOptDescr
Flag
(Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe AskLongComment
-> LookFor -> Maybe String -> WithContext -> DiffAlgorithm -> a)
(Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe AskLongComment
-> LookFor -> Maybe String -> WithContext -> DiffAlgorithm -> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> 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 AskLongComment
-> LookFor -> Maybe String -> WithContext -> DiffAlgorithm -> a)
(Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
PrimDarcsOption Bool
O.askDeps
OptSpec
DarcsOptDescr
Flag
(Maybe AskLongComment
-> LookFor -> Maybe String -> WithContext -> DiffAlgorithm -> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
Flag
(LookFor -> Maybe String -> WithContext -> DiffAlgorithm -> a)
(Maybe AskLongComment
-> LookFor -> Maybe String -> WithContext -> DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
Flag
(LookFor -> Maybe String -> WithContext -> DiffAlgorithm -> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> 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 -> Maybe String -> WithContext -> DiffAlgorithm -> a)
(Maybe AskLongComment
-> LookFor -> Maybe String -> WithContext -> DiffAlgorithm -> a)
PrimDarcsOption (Maybe AskLongComment)
O.askLongComment
OptSpec
DarcsOptDescr
Flag
(LookFor -> Maybe String -> WithContext -> DiffAlgorithm -> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe String -> WithContext -> DiffAlgorithm -> a)
(LookFor -> Maybe String -> WithContext -> DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
Flag
(Maybe String -> WithContext -> DiffAlgorithm -> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> 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 -> WithContext -> DiffAlgorithm -> a)
(LookFor -> Maybe String -> WithContext -> DiffAlgorithm -> a)
PrimDarcsOption LookFor
O.lookfor
OptSpec
DarcsOptDescr
Flag
(Maybe String -> WithContext -> DiffAlgorithm -> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
Flag
(WithContext -> DiffAlgorithm -> a)
(Maybe String -> WithContext -> DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
Flag
(WithContext -> DiffAlgorithm -> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> 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
(WithContext -> DiffAlgorithm -> a)
(Maybe String -> WithContext -> DiffAlgorithm -> a)
PrimDarcsOption (Maybe String)
O.repoDir
OptSpec
DarcsOptDescr
Flag
(WithContext -> DiffAlgorithm -> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
Flag
(DiffAlgorithm -> a)
(WithContext -> DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
Flag
(DiffAlgorithm -> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> 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 -> a)
(WithContext -> DiffAlgorithm -> a)
PrimDarcsOption WithContext
O.withContext
OptSpec
DarcsOptDescr
Flag
(DiffAlgorithm -> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
-> OptSpec DarcsOptDescr Flag a (DiffAlgorithm -> a)
-> DarcsOption
a
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> 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 (DiffAlgorithm -> a)
PrimDarcsOption DiffAlgorithm
O.diffAlgorithm
recordAdvancedOpts :: DarcsOption a
(O.Logfile -> O.Compression -> O.UseIndex -> O.UMask -> O.SetScriptsExecutable -> O.IncludeBoring -> a)
recordAdvancedOpts :: DarcsOption
a
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> a)
recordAdvancedOpts = PrimOptSpec
DarcsOptDescr
Flag
(Compression
-> UseIndex -> UMask -> SetScriptsExecutable -> IncludeBoring -> a)
Logfile
PrimDarcsOption Logfile
O.logfile PrimOptSpec
DarcsOptDescr
Flag
(Compression
-> UseIndex -> UMask -> SetScriptsExecutable -> IncludeBoring -> a)
Logfile
-> OptSpec
DarcsOptDescr
Flag
(UseIndex -> UMask -> SetScriptsExecutable -> IncludeBoring -> a)
(Compression
-> UseIndex -> UMask -> SetScriptsExecutable -> IncludeBoring -> a)
-> OptSpec
DarcsOptDescr
Flag
(UseIndex -> UMask -> SetScriptsExecutable -> IncludeBoring -> a)
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> 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
(UseIndex -> UMask -> SetScriptsExecutable -> IncludeBoring -> a)
(Compression
-> UseIndex -> UMask -> SetScriptsExecutable -> IncludeBoring -> a)
PrimDarcsOption Compression
O.compress OptSpec
DarcsOptDescr
Flag
(UseIndex -> UMask -> SetScriptsExecutable -> IncludeBoring -> a)
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> a)
-> OptSpec
DarcsOptDescr
Flag
(UMask -> SetScriptsExecutable -> IncludeBoring -> a)
(UseIndex -> UMask -> SetScriptsExecutable -> IncludeBoring -> a)
-> OptSpec
DarcsOptDescr
Flag
(UMask -> SetScriptsExecutable -> IncludeBoring -> a)
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> 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
(UMask -> SetScriptsExecutable -> IncludeBoring -> a)
(UseIndex -> UMask -> SetScriptsExecutable -> IncludeBoring -> a)
PrimDarcsOption UseIndex
O.useIndex OptSpec
DarcsOptDescr
Flag
(UMask -> SetScriptsExecutable -> IncludeBoring -> a)
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> a)
-> OptSpec
DarcsOptDescr
Flag
(SetScriptsExecutable -> IncludeBoring -> a)
(UMask -> SetScriptsExecutable -> IncludeBoring -> a)
-> OptSpec
DarcsOptDescr
Flag
(SetScriptsExecutable -> IncludeBoring -> a)
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> 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
(SetScriptsExecutable -> IncludeBoring -> a)
(UMask -> SetScriptsExecutable -> IncludeBoring -> a)
PrimDarcsOption UMask
O.umask OptSpec
DarcsOptDescr
Flag
(SetScriptsExecutable -> IncludeBoring -> a)
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> a)
-> OptSpec
DarcsOptDescr
Flag
(IncludeBoring -> a)
(SetScriptsExecutable -> IncludeBoring -> a)
-> OptSpec
DarcsOptDescr
Flag
(IncludeBoring -> a)
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> 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
(IncludeBoring -> a)
(SetScriptsExecutable -> IncludeBoring -> a)
PrimDarcsOption SetScriptsExecutable
O.setScriptsExecutable OptSpec
DarcsOptDescr
Flag
(IncludeBoring -> a)
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> a)
-> OptSpec DarcsOptDescr Flag a (IncludeBoring -> a)
-> DarcsOption
a
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> 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
data RecordConfig = RecordConfig
{ RecordConfig -> Maybe String
patchname :: Maybe String
, RecordConfig -> Maybe String
author :: Maybe String
, RecordConfig -> TestChanges
testChanges :: O.TestChanges
, RecordConfig -> Maybe Bool
interactive :: Maybe Bool
, RecordConfig -> Bool
pipe :: Bool
, RecordConfig -> Bool
askDeps :: Bool
, :: Maybe O.AskLongComment
, RecordConfig -> LookFor
lookfor :: O.LookFor
, RecordConfig -> Maybe String
_workingRepoDir :: Maybe String
, RecordConfig -> WithContext
withContext :: O.WithContext
, RecordConfig -> DiffAlgorithm
diffAlgorithm :: O.DiffAlgorithm
, RecordConfig -> Verbosity
verbosity :: O.Verbosity
, RecordConfig -> Logfile
logfile :: O.Logfile
, RecordConfig -> Compression
compress :: O.Compression
, RecordConfig -> UseIndex
useIndex :: O.UseIndex
, RecordConfig -> UMask
umask :: O.UMask
, RecordConfig -> SetScriptsExecutable
sse :: O.SetScriptsExecutable
, RecordConfig -> IncludeBoring
includeBoring :: O.IncludeBoring
, RecordConfig -> UseCache
useCache :: O.UseCache
}
recordConfig :: [DarcsFlag] -> RecordConfig
recordConfig :: [Flag] -> RecordConfig
recordConfig = OptSpec
DarcsOptDescr
Flag
RecordConfig
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
-> (Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
-> [Flag]
-> RecordConfig
forall (d :: * -> *) f a b. OptSpec d f a b -> b -> [f] -> a
oparse (DarcsOption
(Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
forall a.
DarcsOption
a
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
recordBasicOpts DarcsOption
(Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
-> OptSpec
DarcsOptDescr
Flag
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
(Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
-> OptSpec
DarcsOptDescr
Flag
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
Flag
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
(Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
PrimDarcsOption Verbosity
O.verbosity OptSpec
DarcsOptDescr
Flag
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
-> OptSpec
DarcsOptDescr
Flag
(UseCache -> RecordConfig)
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
-> OptSpec
DarcsOptDescr
Flag
(UseCache -> RecordConfig)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
Flag
(UseCache -> RecordConfig)
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
forall a.
DarcsOption
a
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> a)
recordAdvancedOpts OptSpec
DarcsOptDescr
Flag
(UseCache -> RecordConfig)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
-> OptSpec
DarcsOptDescr Flag RecordConfig (UseCache -> RecordConfig)
-> OptSpec
DarcsOptDescr
Flag
RecordConfig
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec DarcsOptDescr Flag RecordConfig (UseCache -> RecordConfig)
PrimDarcsOption UseCache
O.useCache) Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> RecordConfig
RecordConfig
record :: DarcsCommand
record :: DarcsCommand
record = 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
"record"
, commandHelp :: Doc
commandHelp = Doc
recordHelp
, commandDescription :: String
commandDescription = String
"Create a patch from unrecorded changes."
, commandExtraArgs :: Int
commandExtraArgs = -Int
1
, commandExtraArgHelp :: [String]
commandExtraArgHelp = [String
"[FILE or DIRECTORY]..."]
, commandCommand :: (AbsolutePath, AbsolutePath) -> [Flag] -> [String] -> IO ()
commandCommand = (AbsolutePath, AbsolutePath) -> [Flag] -> [String] -> IO ()
recordCmd
, commandPrereq :: [Flag] -> IO (Either String ())
commandPrereq = [Flag] -> IO (Either String ())
amInHashedRepository
, 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
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> Any)
-> [DarcsOptDescr Flag]
forall (d :: * -> *) f a b. OptSpec d f a b -> [d f]
odesc OptSpec
DarcsOptDescr
Flag
Any
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> Any)
forall a.
DarcsOption
a
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> a)
recordAdvancedOpts
, commandBasicOptions :: [DarcsOptDescr Flag]
commandBasicOptions = OptSpec
DarcsOptDescr
Flag
Any
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Any)
-> [DarcsOptDescr Flag]
forall (d :: * -> *) f a b. OptSpec d f a b -> [d f]
odesc OptSpec
DarcsOptDescr
Flag
Any
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Any)
forall a.
DarcsOption
a
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
recordBasicOpts
, commandDefaults :: [Flag]
commandDefaults = OptSpec
DarcsOptDescr
Flag
[Flag]
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> [Flag])
-> [Flag]
forall (d :: * -> *) f b. OptSpec d f [f] b -> [f]
defaultFlags OptSpec
DarcsOptDescr
Flag
[Flag]
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> [Flag])
forall a.
DarcsOption
a
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
recordOpts
, commandCheckOptions :: [Flag] -> [String]
commandCheckOptions = OptSpec
DarcsOptDescr
Flag
Any
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> 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 String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> Any)
forall a.
DarcsOption
a
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
recordOpts
}
where
recordOpts :: DarcsOption
a
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
recordOpts = DarcsOption
(Maybe StdCmdAction
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
forall a.
DarcsOption
a
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> a)
recordBasicOpts DarcsOption
(Maybe StdCmdAction
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
-> DarcsOption
(UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
-> DarcsOption
a
(Maybe String
-> Maybe String
-> TestChanges
-> Maybe Bool
-> Bool
-> Bool
-> Maybe AskLongComment
-> LookFor
-> Maybe String
-> WithContext
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> 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)
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> UseCache
-> HooksConfig
-> Bool
-> Bool
-> Bool
-> a)
forall a.
DarcsOption
a
(Logfile
-> Compression
-> UseIndex
-> UMask
-> SetScriptsExecutable
-> IncludeBoring
-> a)
recordAdvancedOpts
commit :: DarcsCommand
commit :: DarcsCommand
commit = String -> Maybe DarcsCommand -> DarcsCommand -> DarcsCommand
commandAlias String
"commit" Maybe DarcsCommand
forall a. Maybe a
Nothing DarcsCommand
record
reportNonExisting :: ScanKnown -> ([AnchoredPath], [AnchoredPath]) -> IO ()
reportNonExisting :: ScanKnown -> ([AnchoredPath], [AnchoredPath]) -> IO ()
reportNonExisting ScanKnown
scan ([AnchoredPath]
paths_only_in_working, [AnchoredPath]
_) = do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ScanKnown
scan ScanKnown -> ScanKnown -> Bool
forall a. Eq a => a -> a -> Bool
/= ScanKnown
ScanKnown Bool -> Bool -> Bool
|| [AnchoredPath] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [AnchoredPath]
paths_only_in_working) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Doc -> IO ()
putDocLn (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$
Doc
"These paths are not yet in the repository and will be added:" Doc -> Doc -> Doc
<+>
[String] -> Doc
pathlist ((AnchoredPath -> String) -> [AnchoredPath] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map AnchoredPath -> String
displayPath [AnchoredPath]
paths_only_in_working)
recordCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
recordCmd :: (AbsolutePath, AbsolutePath) -> [Flag] -> [String] -> IO ()
recordCmd (AbsolutePath, AbsolutePath)
fps [Flag]
flags [String]
args = do
let cfg :: RecordConfig
cfg = [Flag] -> RecordConfig
recordConfig [Flag]
flags
Maybe String -> Bool -> IO ()
checkNameIsNotOption (RecordConfig -> Maybe String
patchname RecordConfig
cfg) (RecordConfig -> Bool
isInteractive RecordConfig
cfg)
DryRun -> UseCache -> UpdatePending -> UMask -> RepoJob () -> IO ()
forall a.
DryRun -> UseCache -> UpdatePending -> UMask -> RepoJob a -> IO a
withRepoLock DryRun
NoDryRun (RecordConfig -> UseCache
useCache RecordConfig
cfg) UpdatePending
YesUpdatePending (RecordConfig -> UMask
umask RecordConfig
cfg) (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
repository :: Repository rt p wR wU wR) -> do
let scan :: ScanKnown
scan = LookForAdds -> IncludeBoring -> ScanKnown
scanKnown (LookFor -> LookForAdds
O.adds (RecordConfig -> LookFor
lookfor RecordConfig
cfg)) (RecordConfig -> IncludeBoring
includeBoring RecordConfig
cfg)
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
repository (RecordConfig -> Verbosity
verbosity RecordConfig
cfg) (RecordConfig -> UseIndex
useIndex RecordConfig
cfg) ScanKnown
scan (LookFor -> LookForMoves
O.moves (RecordConfig -> LookFor
lookfor RecordConfig
cfg)))
Maybe [AnchoredPath]
files
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (RecordConfig -> Verbosity
verbosity RecordConfig
cfg Verbosity -> Verbosity -> Bool
forall a. Eq a => a -> a -> Bool
/= Verbosity
O.Quiet) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
(([AnchoredPath], [AnchoredPath]) -> IO ())
-> Maybe ([AnchoredPath], [AnchoredPath]) -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (ScanKnown -> ([AnchoredPath], [AnchoredPath]) -> IO ()
reportNonExisting ScanKnown
scan) Maybe ([AnchoredPath], [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''
Verbosity -> Maybe [AnchoredPath] -> String -> IO ()
announceFiles (RecordConfig -> Verbosity
verbosity RecordConfig
cfg) Maybe [AnchoredPath]
existing_files String
"Recording changes in"
String -> IO ()
debugMessage String
"About to get the unrecorded changes."
(:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU
changes <- (UseIndex, ScanKnown, DiffAlgorithm)
-> LookForMoves
-> LookForReplaces
-> Repository rt p wR wU wR
-> Maybe [AnchoredPath]
-> IO ((:>) (FL (PrimOf p)) (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)) (FL (PrimOf p)) wR wU)
readPendingAndWorking (RecordConfig -> (UseIndex, ScanKnown, DiffAlgorithm)
diffingOpts RecordConfig
cfg)
(LookFor -> LookForMoves
O.moves (RecordConfig -> LookFor
lookfor RecordConfig
cfg)) (LookFor -> LookForReplaces
O.replaces (RecordConfig -> LookFor
lookfor RecordConfig
cfg))
Repository rt p wR wU wR
repository Maybe [AnchoredPath]
existing_files
String -> IO ()
debugMessage String
"I've got unrecorded changes."
case (:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU
changes of
FL (PrimOf p) wR wZ
NilFL :> FL (PrimOf p) wZ wU
NilFL | Bool -> Bool
not (RecordConfig -> Bool
askDeps RecordConfig
cfg) -> do
IO String -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Bool -> IO String
getDate (RecordConfig -> Bool
pipe RecordConfig
cfg))
String -> IO ()
putStrLn String
"No changes!"
IO ()
forall a. IO a
exitFailure
(:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU
_ -> Repository rt p wR wU wR
-> RecordConfig
-> Maybe [AnchoredPath]
-> (:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU
-> IO ()
forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
(IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wR wU wR
-> RecordConfig
-> Maybe [AnchoredPath]
-> (:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU
-> IO ()
doRecord Repository rt p wR wU wR
repository RecordConfig
cfg Maybe [AnchoredPath]
existing_files (:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU
changes
checkNameIsNotOption :: Maybe String -> Bool -> IO ()
checkNameIsNotOption :: Maybe String -> Bool -> IO ()
checkNameIsNotOption Maybe String
Nothing Bool
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkNameIsNotOption Maybe String
_ Bool
False = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkNameIsNotOption (Just String
name) Bool
True =
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
name Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 Bool -> Bool -> Bool
|| (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
name Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2 Bool -> Bool -> Bool
&& String -> Char
forall a. [a] -> a
head String
name Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-')) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Bool
confirmed <- String -> IO Bool
promptYorn (String -> IO Bool) -> String -> IO Bool
forall a b. (a -> b) -> a -> b
$ String
"You specified " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" as the patch name. Is that really what you want?"
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
confirmed (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
putStrLn String
"Okay, aborting the record." IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
forall a. IO a
exitFailure
doRecord :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree)
=> Repository rt p wR wU wR -> RecordConfig -> Maybe [AnchoredPath]
-> (FL (PrimOf p) :> FL (PrimOf p)) wR wU -> IO ()
doRecord :: Repository rt p wR wU wR
-> RecordConfig
-> Maybe [AnchoredPath]
-> (:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU
-> IO ()
doRecord Repository rt p wR wU wR
repository RecordConfig
cfg Maybe [AnchoredPath]
files pw :: (:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU
pw@(FL (PrimOf p) wR wZ
pending :> FL (PrimOf p) wZ wU
working) = do
String
date <- Bool -> IO String
getDate (RecordConfig -> Bool
pipe RecordConfig
cfg)
String
my_author <- Maybe String -> Bool -> IO String
getAuthor (RecordConfig -> Maybe String
author RecordConfig
cfg) (RecordConfig -> Bool
pipe RecordConfig
cfg)
String -> IO ()
debugMessage String
"I'm slurping the repository."
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
repository
String -> IO ()
debugMessage String
"About to select changes..."
(FL (PrimOf p) wR wZ
chs :> FL (PrimOf p) wZ wU
_ ) <- FL (PrimOf p) wR wU
-> SelectionConfig (PrimOf p)
-> IO ((:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU)
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)
runInvertibleSelection (FL (PrimOf p) wR wU -> FL (PrimOf p) wR wU
forall (prim :: * -> * -> *) wX wY.
PrimCanonize prim =>
FL prim wX wY -> FL prim wX wY
sortCoalesceFL (FL (PrimOf p) wR wU -> FL (PrimOf p) wR wU)
-> FL (PrimOf p) wR wU -> FL (PrimOf p) wR wU
forall a b. (a -> b) -> a -> b
$ FL (PrimOf p) wR wZ
pending FL (PrimOf p) wR wZ -> FL (PrimOf p) wZ wU -> FL (PrimOf p) wR wU
forall (a :: * -> * -> *) wX wY wZ.
FL a wX wY -> FL a wY wZ -> FL a wX wZ
+>+ FL (PrimOf p) wZ wU
working) (SelectionConfig (PrimOf p)
-> IO ((:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU))
-> SelectionConfig (PrimOf p)
-> IO ((:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU)
forall a b. (a -> b) -> a -> b
$
WhichChanges
-> String
-> PatchSelectionOptions
-> Maybe (Splitter (PrimOf p))
-> Maybe [AnchoredPath]
-> Maybe (Tree IO)
-> SelectionConfig (PrimOf p)
forall (prim :: * -> * -> *).
WhichChanges
-> String
-> PatchSelectionOptions
-> Maybe (Splitter prim)
-> Maybe [AnchoredPath]
-> Maybe (Tree IO)
-> SelectionConfig prim
selectionConfigPrim
WhichChanges
First String
"record" (RecordConfig -> PatchSelectionOptions
patchSelOpts RecordConfig
cfg)
(Splitter (PrimOf p) -> Maybe (Splitter (PrimOf p))
forall a. a -> Maybe a
Just (DiffAlgorithm -> Splitter (PrimOf p)
forall (p :: * -> * -> *).
PrimPatch p =>
DiffAlgorithm -> Splitter p
primSplitter (RecordConfig -> DiffAlgorithm
diffAlgorithm RecordConfig
cfg)))
Maybe [AnchoredPath]
files (Tree IO -> Maybe (Tree IO)
forall a. a -> Maybe a
Just Tree IO
pristine)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (RecordConfig -> Bool
askDeps RecordConfig
cfg) Bool -> Bool -> Bool
&& FL (PrimOf p) wR wZ -> Bool
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> Bool
nullFL FL (PrimOf p) wR wZ
chs) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
do String -> IO ()
putStrLn String
"Ok, if you don't want to record anything, that's fine!"
IO ()
forall a. IO a
exitSuccess
(ExitCode -> Maybe ()) -> (() -> IO ()) -> IO () -> IO ()
forall e b a.
Exception e =>
(e -> Maybe b) -> (b -> IO a) -> IO a -> IO a
handleJust ExitCode -> Maybe ()
onlySuccessfulExits (\()
_ -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
do [PatchInfo]
deps <- if RecordConfig -> Bool
askDeps RecordConfig
cfg
then Repository rt p wR wU wR
-> FL (PrimOf p) wR wZ
-> PatchSelectionOptions
-> [PatchInfo]
-> IO [PatchInfo]
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT wY.
(IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wR wU wT
-> FL (PrimOf p) wT wY
-> PatchSelectionOptions
-> [PatchInfo]
-> IO [PatchInfo]
askAboutDepends Repository rt p wR wU wR
repository FL (PrimOf p) wR wZ
chs (RecordConfig -> PatchSelectionOptions
patchSelOpts RecordConfig
cfg) []
else [PatchInfo] -> IO [PatchInfo]
forall (m :: * -> *) a. Monad m => a -> m a
return []
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (RecordConfig -> Bool
askDeps RecordConfig
cfg) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
debugMessage String
"I've asked about dependencies."
if FL (PrimOf p) wR wZ -> Bool
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> Bool
nullFL FL (PrimOf p) wR wZ
chs Bool -> Bool -> Bool
&& [PatchInfo] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [PatchInfo]
deps
then String -> IO ()
putStrLn String
"Ok, if you don't want to record anything, that's fine!"
else do FL (PrimOf p) wR wZ -> IO ()
forall (p :: * -> * -> *) wX wY. PatchInspect p => p wX wY -> IO ()
setEnvDarcsFiles FL (PrimOf p) wR wZ
chs
(String
name, [String]
my_log, Maybe String
logf) <- Maybe String
-> Bool
-> Logfile
-> Maybe AskLongComment
-> Maybe (String, [String])
-> FL (PrimOf p) wR wZ
-> IO (String, [String], Maybe String)
forall (prim :: * -> * -> *) wX wY.
PrimPatch prim =>
Maybe String
-> Bool
-> Logfile
-> Maybe AskLongComment
-> Maybe (String, [String])
-> FL prim wX wY
-> IO (String, [String], Maybe String)
getLog (RecordConfig -> Maybe String
patchname RecordConfig
cfg) (RecordConfig -> Bool
pipe RecordConfig
cfg) (RecordConfig -> Logfile
logfile RecordConfig
cfg) (RecordConfig -> Maybe AskLongComment
askLongComment RecordConfig
cfg) Maybe (String, [String])
forall a. Maybe a
Nothing FL (PrimOf p) wR wZ
chs
String -> IO ()
debugMessage (String
"Patch name as received from getLog: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [Int] -> String
forall a. Show a => a -> String
show ((Char -> Int) -> String -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Int
ord String
name))
Repository rt p wR wU wR
-> RecordConfig
-> String
-> String
-> String
-> [String]
-> Maybe String
-> [PatchInfo]
-> FL (PrimOf p) wR wZ
-> (:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU
-> IO ()
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wX.
(IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wR wU wR
-> RecordConfig
-> String
-> String
-> String
-> [String]
-> Maybe String
-> [PatchInfo]
-> FL (PrimOf p) wR wX
-> (:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU
-> IO ()
doActualRecord Repository rt p wR wU wR
repository RecordConfig
cfg String
name String
date String
my_author [String]
my_log Maybe String
logf [PatchInfo]
deps FL (PrimOf p) wR wZ
chs (:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU
pw
doActualRecord :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree)
=> Repository rt p wR wU wR
-> RecordConfig
-> String -> String -> String
-> [String] -> Maybe String
-> [PatchInfo] -> FL (PrimOf p) wR wX
-> (FL (PrimOf p) :> FL (PrimOf p)) wR wU -> IO ()
doActualRecord :: Repository rt p wR wU wR
-> RecordConfig
-> String
-> String
-> String
-> [String]
-> Maybe String
-> [PatchInfo]
-> FL (PrimOf p) wR wX
-> (:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU
-> IO ()
doActualRecord Repository rt p wR wU wR
_repository RecordConfig
cfg String
name String
date String
my_author [String]
my_log Maybe String
logf [PatchInfo]
deps FL (PrimOf p) wR wX
chs
(FL (PrimOf p) wR wZ
pending :> FL (PrimOf p) wZ wU
working) = do
String -> IO ()
debugMessage String
"Writing the patch file..."
PatchInfo
myinfo <- String -> String -> String -> [String] -> IO PatchInfo
patchinfo String
date String
name String
my_author [String]
my_log
let mypatch :: Named p wR wX
mypatch = PatchInfo -> FL (PrimOf p) wR wX -> Named p wR wX
forall (p :: * -> * -> *) wX wY.
FromPrim p =>
PatchInfo -> FL (PrimOf p) wX wY -> Named p wX wY
infopatch PatchInfo
myinfo (FL (PrimOf p) wR wX -> Named p wR wX)
-> FL (PrimOf p) wR wX -> Named p wR wX
forall a b. (a -> b) -> a -> b
$ String -> FL (PrimOf p) wR wX -> FL (PrimOf p) wR wX
forall (a :: * -> * -> *) wX wY. String -> FL a wX wY -> FL a wX wY
progressFL String
"Writing changes:" FL (PrimOf p) wR wX
chs
let pia :: PatchInfoAndG rt (Named p) wR wX
pia = Named p wR wX -> PatchInfoAndG rt (Named p) wR wX
forall (p :: * -> * -> *) wX wY (rt :: RepoType).
(Ident p, PatchId p ~ PatchInfo) =>
p wX wY -> PatchInfoAndG rt p wX wY
n2pia (Named p wR wX -> PatchInfoAndG rt (Named p) wR wX)
-> Named p wR wX -> PatchInfoAndG rt (Named p) wR wX
forall a b. (a -> b) -> a -> b
$ Named p wR wX -> [PatchInfo] -> Named p wR wX
forall (p :: * -> * -> *) wX wY.
Named p wX wY -> [PatchInfo] -> Named p wX wY
adddeps Named p wR wX
mypatch [PatchInfo]
deps
Repository rt p wR wU wX
_repository <-
Repository rt p wR wU wR
-> Compression
-> Verbosity
-> UpdatePending
-> PatchInfoAnd rt p wR wX
-> IO (Repository rt p wR wU wX)
forall (p :: * -> * -> *) (rt :: RepoType) wR wU wT wY.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wR wU wT
-> Compression
-> Verbosity
-> UpdatePending
-> PatchInfoAnd rt p wT wY
-> IO (Repository rt p wR wU wY)
tentativelyAddPatch Repository rt p wR wU wR
_repository (RecordConfig -> Compression
compress RecordConfig
cfg) (RecordConfig -> Verbosity
verbosity RecordConfig
cfg)
UpdatePending
NoUpdatePending PatchInfoAnd rt p wR wX
forall (rt :: RepoType). PatchInfoAndG rt (Named p) wR wX
pia
Repository rt p wR wU wX -> IO ()
forall t. t -> IO ()
invalidateIndex Repository rt p wR wU wX
_repository
String -> IO ()
debugMessage String
"Applying to pristine..."
Repository rt p wR wU wX
-> Verbosity
-> TestChanges
-> SetScriptsExecutable
-> Bool
-> String
-> String
-> Maybe String
-> IO ()
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
Repository rt p wR wU wT
-> Verbosity
-> TestChanges
-> SetScriptsExecutable
-> Bool
-> String
-> String
-> Maybe String
-> IO ()
testTentativeAndMaybeExit Repository rt p wR wU wX
_repository (RecordConfig -> Verbosity
verbosity RecordConfig
cfg) (RecordConfig -> TestChanges
testChanges RecordConfig
cfg)
(RecordConfig -> SetScriptsExecutable
sse RecordConfig
cfg) (RecordConfig -> Bool
isInteractive RecordConfig
cfg) (String
"you have a bad patch: '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'")
String
"record it" (String -> Maybe String
forall a. a -> Maybe a
Just String
failuremessage)
Repository rt p wR wU wX
-> FL (PrimOf p) wR wX
-> FL (PrimOf p) wR wZ
-> FL (PrimOf p) wZ wU
-> IO ()
forall (rt :: RepoType) (p :: * -> * -> *) wR wO wT wP wU.
RepoPatch p =>
Repository rt p wR wU wT
-> FL (PrimOf p) wO wT
-> FL (PrimOf p) wO wP
-> FL (PrimOf p) wP wU
-> IO ()
tentativelyRemoveFromPW Repository rt p wR wU wX
_repository FL (PrimOf p) wR wX
chs FL (PrimOf p) wR wZ
pending FL (PrimOf p) wZ wU
working
Repository rt p wX wU wX
_repository <-
Repository rt p wR wU wX
-> UpdatePending -> Compression -> IO (Repository rt p wX wU wX)
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
(IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wR wU wT
-> UpdatePending -> Compression -> IO (Repository rt p wT wU wT)
finalizeRepositoryChanges Repository rt p wR wU wX
_repository UpdatePending
YesUpdatePending (RecordConfig -> Compression
compress RecordConfig
cfg)
IO (Repository rt p wX wU wX)
-> String -> IO (Repository rt p wX wU wX)
forall a. IO a -> String -> IO a
`clarifyErrors` String
failuremessage
String -> IO ()
debugMessage String
"Syncing timestamps..."
Maybe String -> IO ()
removeLogFile Maybe String
logf
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (RecordConfig -> Verbosity
verbosity RecordConfig
cfg Verbosity -> Verbosity -> Bool
forall a. Eq a => a -> a -> Bool
== Verbosity
O.Quiet) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
Doc -> IO ()
putDocLn (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ String
"Finished recording patch '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'"
FL (PatchInfoAnd Any p) wR wX -> IO ()
forall (p :: * -> * -> *) (rt :: RepoType) wX wY.
RepoPatch p =>
FL (PatchInfoAnd rt p) wX wY -> IO ()
setEnvDarcsPatches (PatchInfoAndG Any (Named p) wR wX
forall (rt :: RepoType). PatchInfoAndG rt (Named p) wR wX
pia PatchInfoAndG Any (Named p) wR wX
-> FL (PatchInfoAnd Any p) wX wX -> FL (PatchInfoAnd Any p) wR wX
forall (a :: * -> * -> *) wX wY wZ.
a wX wY -> FL a wY wZ -> FL a wX wZ
:>: FL (PatchInfoAnd Any p) wX wX
forall (a :: * -> * -> *) wX. FL a wX wX
NilFL)
where
removeLogFile :: Maybe String -> IO ()
removeLogFile :: Maybe String -> IO ()
removeLogFile Maybe String
Nothing = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
removeLogFile (Just String
lf)
| String
lf String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
darcsLastMessage = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> IO ()
removeFile String
lf
failuremessage :: String
failuremessage =
String
"Failed to record patch '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'" String -> String -> String
forall a. [a] -> [a] -> [a]
++
case Maybe String
logf of
Just String
lf -> String
"\nLogfile left in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
lf String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"."
Maybe String
Nothing -> String
""
onlySuccessfulExits :: ExitCode -> Maybe ()
onlySuccessfulExits :: ExitCode -> Maybe ()
onlySuccessfulExits ExitCode
ExitSuccess = () -> Maybe ()
forall a. a -> Maybe a
Just ()
onlySuccessfulExits ExitCode
_ = Maybe ()
forall a. Maybe a
Nothing
patchSelOpts :: RecordConfig -> S.PatchSelectionOptions
patchSelOpts :: RecordConfig -> PatchSelectionOptions
patchSelOpts RecordConfig
cfg = PatchSelectionOptions :: Verbosity
-> [MatchFlag]
-> Bool
-> SelectDeps
-> WithSummary
-> WithContext
-> PatchSelectionOptions
S.PatchSelectionOptions
{ verbosity :: Verbosity
S.verbosity = RecordConfig -> Verbosity
verbosity RecordConfig
cfg
, matchFlags :: [MatchFlag]
S.matchFlags = []
, interactive :: Bool
S.interactive = RecordConfig -> Bool
isInteractive RecordConfig
cfg
, selectDeps :: SelectDeps
S.selectDeps = SelectDeps
O.PromptDeps
, withSummary :: WithSummary
S.withSummary = WithSummary
O.NoSummary
, withContext :: WithContext
S.withContext = RecordConfig -> WithContext
withContext RecordConfig
cfg
}
diffingOpts :: RecordConfig -> (O.UseIndex, O.ScanKnown, O.DiffAlgorithm)
diffingOpts :: RecordConfig -> (UseIndex, ScanKnown, DiffAlgorithm)
diffingOpts RecordConfig
cfg = UseIndex
-> LookForAdds
-> IncludeBoring
-> DiffAlgorithm
-> (UseIndex, ScanKnown, DiffAlgorithm)
diffOpts (RecordConfig -> UseIndex
useIndex RecordConfig
cfg) (LookFor -> LookForAdds
O.adds (RecordConfig -> LookFor
lookfor RecordConfig
cfg)) IncludeBoring
O.NoIncludeBoring (RecordConfig -> DiffAlgorithm
diffAlgorithm RecordConfig
cfg)
isInteractive :: RecordConfig -> Bool
isInteractive :: RecordConfig -> Bool
isInteractive = Bool -> (Bool -> Bool) -> Maybe Bool -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True Bool -> Bool
forall a. a -> a
id (Maybe Bool -> Bool)
-> (RecordConfig -> Maybe Bool) -> RecordConfig -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RecordConfig -> Maybe Bool
interactive