Find git executable at run time
[git-darcs-import.git] / src / Darcs / Arguments.lhs
blob5c9eead77efdc4acc2913fe1165e361aa65b05c1
1 % Copyright (C) 2002-2004 David Roundy
3 % This program is free software; you can redistribute it and/or modify
4 % it under the terms of the GNU General Public License as published by
5 % the Free Software Foundation; either version 2, or (at your option)
6 % any later version.
8 % This program is distributed in the hope that it will be useful,
9 % but WITHOUT ANY WARRANTY; without even the implied warranty of
10 % MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11 % GNU General Public License for more details.
13 % You should have received a copy of the GNU General Public License
14 % along with this program; see the file COPYING. If not, write to
15 % the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
16 % Boston, MA 02110-1301, USA.
18 \begin{code}
19 {-# OPTIONS_GHC -cpp #-}
20 {-# LANGUAGE CPP #-}
22 #include "gadts.h"
24 module Darcs.Arguments ( DarcsFlag( .. ), isa, isAnAbsolute, isAnAbsoluteOrStd, flagToString,
25 isin, arein,
26 definePatches, defineChanges,
27 fixFilePath, fixFilePathOrStd, fixUrl,
28 fixSubPaths, areFileArgs,
29 DarcsOption( .. ), option_from_darcsoption,
30 help, list_options, list_files,
31 help_on_match,
32 any_verbosity, disable, restrict_paths,
33 notest, test, working_repo_dir,
34 remote_repo, get_remote_repo,
35 leave_test_dir,
36 possibly_remote_repo_dir, get_repodir, get_repourl,
37 list_registered_files, list_unregistered_files,
38 author, get_author, get_easy_author, get_sendmail_cmd,
39 patchname_option, distname_option,
40 logfile, rmlogfile, from_opt, subject, get_subject,
41 target, cc, get_cc, output, output_auto_name,
42 recursive, inventory_choices, get_inventory_choices,
43 askdeps, ignoretimes, lookforadds,
44 ask_long_comment, sendmail_cmd,
45 sign, verify, edit_description,
46 reponame, tagname, creatorhash,
47 apply_conflict_options, reply,
48 pull_conflict_options, use_external_merge,
49 deps_sel, nocompress,
50 uncompress_nocompress, repo_combinator,
51 options_latex, reorder_patches,
52 noskip_boring, allow_problematic_filenames,
53 applyas, human_readable,
54 changes_reverse, only_to_files,
55 changes_format, match_one_context, match_one_nontag,
56 send_to_context,
57 get_context,
58 pipe_interactive, all_interactive,
59 all_pipe_interactive,
60 summary, unified, tokens,
61 checkpoint, partial, partial_check,
62 diff_cmd_flag, diffflags, unidiff, xmloutput,
63 force_replace, dry_run, dry_run_noxml,
64 print_dry_run_message_and_exit, showFriendly,
65 match_one, match_several, match_range,
66 match_several_or_range, happy_forwarding,
67 match_several_or_last,
68 set_default,
69 fancy_move_add, pristine_tree,
70 set_scripts_executable,
71 sibling, flagsToSiblings, relink, relink_pristine, nolinks,
72 files, directories, pending,
73 posthook_cmd, posthook_prompt,
74 get_posthook_cmd,
75 prehook_cmd, prehook_prompt,
76 get_prehook_cmd, nullFlag,
77 umask_option,
78 store_in_memory,
79 patch_select_flag,
80 network_options,
81 allow_unrelated_repos
82 ) where
83 import System.Console.GetOpt
84 import System.Directory ( doesDirectoryExist )
85 import Data.List ( (\\), nub )
86 import Data.Maybe ( fromMaybe, listToMaybe )
87 import System.Exit ( ExitCode(ExitSuccess), exitWith )
88 import Data.Maybe ( catMaybes )
89 import Control.Monad ( when, unless )
90 import Data.Char ( isDigit )
91 #ifndef WIN32
92 import Printer ( renderString )
93 import System.Posix.Env ( setEnv )
94 import Darcs.Patch ( list_touched_files )
95 import Darcs.Progress ( beginTedious, endTedious, tediousSize, finishedOneIO )
96 #endif
98 import Darcs.Hopefully ( PatchInfoAnd, info )
99 import Darcs.Patch ( RepoPatch, Patchy, showNicely, description )
100 import Darcs.Patch.Info ( to_xml )
101 import Darcs.Ordered ( FL, mapFL )
102 import qualified Darcs.Patch ( summary )
103 import Darcs.Utils ( askUser, maybeGetEnv, firstNotBlank, firstJustIO,
104 withCurrentDirectory )
105 import Darcs.Repository.Prefs ( boring_file_filter, get_preflist, get_global )
106 import Darcs.URL ( is_file )
107 import Darcs.RepoPath ( AbsolutePath, AbsolutePathOrStd, SubPath, toFilePath,
108 makeSubPathOf, simpleSubPath,
109 ioAbsolute, ioAbsoluteOrStd,
110 makeAbsolute, makeAbsoluteOrStd, rootDirectory )
111 import Darcs.Patch.MatchData ( patch_match )
112 import Darcs.Flags ( DarcsFlag(..) )
113 import Darcs.Repository ( slurp_pending, withRepository, ($-) )
114 import Darcs.Repository.HashedRepo ( slurp_all_but_darcs )
115 import Darcs.SlurpDirectory ( list_slurpy )
116 import Darcs.Global ( darcsdir )
117 import Printer ( Doc, putDocLn, text, vsep, ($$), vcat )
118 import URL ( pipeliningEnabledByDefault )
119 #include "impossible.h"
120 \end{code}
122 \begin{code}
123 data FlagContent = NoContent | AbsoluteContent AbsolutePath | AbsoluteOrStdContent AbsolutePathOrStd | StringContent String
124 deriving (Eq, Show, Ord)
126 -- getContent is very tedious to write, but this is the only way (that
127 -- I know of) to guarantee that it works for all flags (which then
128 -- guarantees that isAnAbsolute, isa, flagToString, etc also work
129 -- properly)
131 -- | 'get_content' returns the content of a flag, if any.
132 -- For instance, the content of @Author \"Louis Aragon\"@ is @StringContent
133 -- \"Louis Aragon\"@, while the content of @Pipe@ is @NoContent@
134 getContent :: DarcsFlag -> FlagContent
135 getContent (PatchName s) = StringContent s
136 getContent (Output s) = AbsoluteOrStdContent s
137 getContent Verbose = NoContent
138 getContent Help = NoContent
139 getContent ListOptions = NoContent
140 getContent Test = NoContent
141 getContent NoTest = NoContent
142 getContent HelpOnMatch = NoContent
143 getContent OnlyChangesToFiles = NoContent
144 getContent LeaveTestDir = NoContent
145 getContent NoLeaveTestDir = NoContent
146 getContent Timings = NoContent
147 getContent Debug = NoContent
148 getContent DebugVerbose = NoContent
149 getContent DebugHTTP = NoContent
150 getContent NormalVerbosity = NoContent
151 getContent Quiet = NoContent
152 getContent (Target s) = StringContent s
153 getContent (Cc s) = StringContent s
154 getContent (Subject s) = StringContent s
155 getContent (SendmailCmd s) = StringContent s
156 getContent (Author s) = StringContent s
157 getContent (OnePatch s) = StringContent s
158 getContent (SeveralPatch s) = StringContent s
159 getContent (AfterPatch s) = StringContent s
160 getContent (UpToPatch s) = StringContent s
161 getContent (TagName s) = StringContent s
162 getContent (LastN s) = StringContent (show s)
163 getContent (OneTag s) = StringContent s
164 getContent (AfterTag s) = StringContent s
165 getContent (UpToTag s) = StringContent s
166 getContent (Context s) = AbsoluteContent s
167 getContent (LogFile s) = AbsoluteContent s
168 getContent (OutputAutoName s) = AbsoluteContent s
169 getContent NumberPatches = NoContent
170 getContent (PatchIndexRange _ _) = NoContent -- FIXME this doesn't fit into a neat category
171 getContent Count = NoContent
172 getContent All = NoContent
173 getContent Recursive = NoContent
174 getContent NoRecursive = NoContent
175 getContent Reorder = NoContent
176 getContent RestrictPaths = NoContent
177 getContent DontRestrictPaths = NoContent
178 getContent AskDeps = NoContent
179 getContent NoAskDeps = NoContent
180 getContent RmLogFile = NoContent
181 getContent (DistName s) = StringContent s
182 getContent (CreatorHash s) = StringContent s
183 getContent (SignAs s) = StringContent s
184 getContent (SignSSL s) = StringContent s
185 getContent (Verify s) = AbsoluteContent s
186 getContent (VerifySSL s) = AbsoluteContent s
187 getContent IgnoreTimes = NoContent
188 getContent LookForAdds = NoContent
189 getContent NoLookForAdds = NoContent
190 getContent AnyOrder = NoContent
191 getContent Intersection = NoContent
192 getContent Unified = NoContent
193 getContent Union = NoContent
194 getContent Complement = NoContent
195 getContent Sign = NoContent
196 getContent NoSign = NoContent
197 getContent HappyForwarding = NoContent
198 getContent SSHControlMaster = NoContent
199 getContent NoSSHControlMaster = NoContent
200 getContent (Toks s) = StringContent s
201 getContent (WorkDir s) = StringContent s
202 getContent (RepoDir s) = StringContent s
203 getContent (RemoteRepo s) = StringContent s
204 getContent (Reply s) = StringContent s
205 getContent EditDescription = NoContent
206 getContent NoEditDescription = NoContent
207 getContent EditLongComment = NoContent
208 getContent NoEditLongComment = NoContent
209 getContent PromptLongComment = NoContent
210 getContent AllowConflicts = NoContent
211 getContent MarkConflicts = NoContent
212 getContent NoAllowConflicts = NoContent
213 getContent Boring = NoContent
214 getContent AllowCaseOnly = NoContent
215 getContent AllowWindowsReserved = NoContent
216 getContent DontGrabDeps = NoContent
217 getContent DontPromptForDependencies = NoContent
218 getContent PromptForDependencies = NoContent
219 getContent Compress = NoContent
220 getContent NoCompress = NoContent
221 getContent UnCompress = NoContent
222 getContent MachineReadable = NoContent
223 getContent HumanReadable = NoContent
224 getContent Pipe = NoContent
225 getContent Interactive = NoContent
226 getContent Summary = NoContent
227 getContent NoSummary = NoContent
228 getContent (ApplyAs s) = StringContent s
229 getContent (DiffCmd s) = StringContent s
230 getContent (ExternalMerge s) = StringContent s
231 getContent (DiffFlags s) = StringContent s
232 getContent (OnePattern _) = NoContent -- FIXME!!!
233 getContent (SeveralPattern _) = NoContent -- FIXME!!!
234 getContent (UpToPattern _) = NoContent -- FIXME!!!
235 getContent (AfterPattern _) = NoContent -- FIXME!!!
236 getContent Reverse = NoContent
237 getContent CheckPoint = NoContent
238 getContent Partial = NoContent
239 getContent Complete = NoContent
240 getContent Lazy = NoContent
241 getContent Ephemeral = NoContent
242 getContent (FixFilePath _ _) = NoContent -- FIXME!!!
243 getContent XMLOutput = NoContent
244 getContent ForceReplace = NoContent
245 getContent NonApply = NoContent
246 getContent NonVerify = NoContent
247 getContent NonForce = NoContent
248 getContent DryRun = NoContent
249 getContent SetDefault = NoContent
250 getContent NoSetDefault = NoContent
251 getContent FancyMoveAdd = NoContent
252 getContent NoFancyMoveAdd = NoContent
253 getContent Disable = NoContent
254 getContent SetScriptsExecutable = NoContent
255 getContent DontSetScriptsExecutable = NoContent
256 getContent UseHashedInventory = NoContent
257 getContent UseOldFashionedInventory = NoContent
258 getContent UseFormat2 = NoContent
259 getContent PristinePlain = NoContent
260 getContent PristineNone = NoContent
261 getContent NoUpdateWorking = NoContent
262 getContent Relink = NoContent
263 getContent RelinkPristine = NoContent
264 getContent NoLinks = NoContent
265 getContent Files = NoContent
266 getContent NoFiles = NoContent
267 getContent Directories = NoContent
268 getContent NoDirectories = NoContent
269 getContent Pending = NoContent
270 getContent NoPending = NoContent
271 getContent NoPosthook = NoContent
272 getContent AskPosthook = NoContent
273 getContent (Sibling s) = AbsoluteContent s
274 getContent (PosthookCmd s) = StringContent s
275 getContent RunPosthook = NoContent
276 getContent NoPrehook = NoContent
277 getContent RunPrehook = NoContent
278 getContent AskPrehook = NoContent
279 getContent StoreInMemory = NoContent
280 getContent HTTPPipelining = NoContent
281 getContent NoHTTPPipelining = NoContent
282 getContent NoCache = NoContent
283 getContent NullFlag = NoContent
284 getContent (PrehookCmd s) = StringContent s
285 getContent (UMask s) = StringContent s
286 getContent AllowUnrelatedRepos = NoContent
288 get_content :: DarcsFlag -> Maybe String
289 get_content f = do StringContent s <- Just $ getContent f
290 return s
292 -- | @a `'isa'` b@ tests whether @a@ is flag @b@ with a string argument.
293 -- @b@ typically is a Flag constructor expecting a string
294 -- For example, @(Author \"Ted Hughes\") `isa` Author@ returns true.
295 isa :: DarcsFlag -> (String -> DarcsFlag) -> Bool
296 a `isa` b = case get_content a of
297 Nothing -> False
298 Just s -> a == b s
300 -- | @a `'isAnAbsolute'` b@ tests whether @a@ is flag @b@ with an absolute path argument.
301 -- @b@ typically is a Flag constructor expecting an absolute path argument
302 -- For example, @(Context contextfile) `isAnAbsolute` Context@ returns true.
303 isAnAbsolute :: DarcsFlag -> (AbsolutePath -> DarcsFlag) -> Bool
304 isAnAbsolute f x = case getContent f of
305 AbsoluteContent s -> f == x s
306 _ -> False
308 -- | @a `'isAnAbsoluteOrStd'` b@ tests whether @a@ is flag @b@ with a path argument.
309 -- @b@ typically is a Flag constructor expecting a path argument
310 -- For example, @(Output o) `isAnAbsoluteOrStd` @ returns true.
311 isAnAbsoluteOrStd :: DarcsFlag -> (AbsolutePathOrStd -> DarcsFlag) -> Bool
312 isAnAbsoluteOrStd f x = case getContent f of
313 AbsoluteOrStdContent s -> f == x s
314 _ -> False
316 isin :: (String->DarcsFlag) -> [DarcsFlag] -> Bool
317 f `isin` fs = any (`isa` f) fs
319 arein :: [DarcsOption] -> [DarcsFlag] -> Bool
320 (DarcsNoArgOption _ _ f _ : dos') `arein` fs
321 = f `elem` fs || dos' `arein` fs
322 (DarcsArgOption _ _ f _ _ : dos') `arein` fs
323 = f `isin` fs || dos' `arein` fs
324 (DarcsAbsPathOption _ _ f _ _ : dos') `arein` fs
325 = any (`isAnAbsolute` f) fs || dos' `arein` fs
326 (DarcsAbsPathOrStdOption _ _ f _ _ : dos') `arein` fs
327 = any (`isAnAbsoluteOrStd` f) fs || dos' `arein` fs
328 (DarcsOptAbsPathOption _ _ _ f _ _ : dos') `arein` fs
329 = any (`isAnAbsolute` f) fs || dos' `arein` fs
330 (DarcsMultipleChoiceOption os: dos') `arein` fs
331 = os `arein` fs || dos' `arein` fs
332 [] `arein` _ = False
334 -- | A type for darcs' options. The value contains the command line
335 -- switch(es) for the option, a help string, and a function to build a
336 -- @DarcsFlag@ from the command line arguments. for each constructor,
337 -- 'shortSwitches' represents the list of short command line switches
338 -- which invoke the option, longSwitches the list of long command line
339 -- switches, optDescr the description of the option, and argDescr the description
340 -- of its argument, if any. mkFlag is a function which makes a @DarcsFlag@ from
341 -- the arguments of the option.
342 data DarcsOption
343 = DarcsArgOption [Char] [String] (String->DarcsFlag) String String
344 -- ^ @DarcsArgOption shortSwitches longSwitches mkFlag ArgDescr OptDescr@
345 -- The constructor for options with a string argument, such as
346 -- @--tag@
348 | DarcsAbsPathOption [Char] [String] (AbsolutePath -> DarcsFlag) String String
349 -- ^ @DarcsAbsPathOption shortSwitches longSwitches mkFlag ArgDescr OptDescr@
350 -- The constructor for options with an absolute path argument, such as
351 -- @--sibling@
353 | DarcsAbsPathOrStdOption [Char] [String] (AbsolutePathOrStd -> DarcsFlag) String String
354 -- ^ @DarcsAbsPathOrStdOption shortSwitches longSwitches mkFlag ArgDescr OptDescr@
355 -- The constructor for options with a path argument, such as @-o@
357 | DarcsOptAbsPathOption [Char] [String] String (AbsolutePath -> DarcsFlag) String String
358 -- ^ @DarcsOptAbsPathOrStdOption shortSwitches longSwitches defaultPath
359 -- mkFlag ArgDescr OptDescr@ where defaultPath is a default value
360 -- for the Path, as a string to be parsed as if it had been given
361 -- on the command line.
362 -- The constructor for options with an optional path argument, such as @-O@
364 | DarcsNoArgOption [Char] [String] DarcsFlag String
365 -- ^ @DarcsNoArgOption shortSwitches longSwitches mkFlag optDescr@
366 -- The constructon fon options with no arguments.
368 | DarcsMultipleChoiceOption [DarcsOption]
369 -- ^ A constructor for grouping related options together, such as
370 -- @--hashed@, @--darcs-2@ and @--old-fashioned-inventory@.
372 option_from_darcsoption :: AbsolutePath -> DarcsOption -> [OptDescr DarcsFlag]
373 option_from_darcsoption _ (DarcsNoArgOption a b c h) = [Option a b (NoArg c) h]
374 option_from_darcsoption _ (DarcsArgOption a b c n h) = [Option a b (ReqArg c n) h]
375 option_from_darcsoption wd (DarcsMultipleChoiceOption os) = concatMap (option_from_darcsoption wd) os
376 option_from_darcsoption wd (DarcsAbsPathOrStdOption a b c n h) = [Option a b (ReqArg (c . makeAbsoluteOrStd wd) n) h]
377 option_from_darcsoption wd (DarcsAbsPathOption a b c n h) = [Option a b (ReqArg (c . makeAbsolute wd) n) h]
378 option_from_darcsoption wd (DarcsOptAbsPathOption a b d c n h) = [Option a b (OptArg (c . makeAbsolute wd . fromMaybe d) n) h]
380 -- | 'concat_option' creates a DarcsMultipleChoicOption from a list of
381 -- option, flattening any DarcsMultipleChoiceOption in the list.
382 concat_options :: [DarcsOption] -> DarcsOption
383 concat_options os = DarcsMultipleChoiceOption $ concatMap from_option os
384 where
385 from_option (DarcsMultipleChoiceOption xs) = xs
386 from_option x = [x]
387 \end{code}
389 \begin{code}
390 extract_fix_path :: [DarcsFlag] -> Maybe (AbsolutePath, AbsolutePath)
391 extract_fix_path [] = Nothing
392 extract_fix_path ((FixFilePath repo orig):_) = Just (repo, orig)
393 extract_fix_path (_:fs) = extract_fix_path fs
395 fixFilePath :: [DarcsFlag] -> FilePath -> IO AbsolutePath
396 fixFilePath opts f = case extract_fix_path opts of
397 Nothing -> bug "Can't fix path in fixFilePath"
398 Just (_,o) -> withCurrentDirectory o $ ioAbsolute f
400 fixFilePathOrStd :: [DarcsFlag] -> FilePath -> IO AbsolutePathOrStd
401 fixFilePathOrStd opts f =
402 case extract_fix_path opts of
403 Nothing -> bug "Can't fix path in fixFilePathOrStd"
404 Just (_,o) -> withCurrentDirectory o $ ioAbsoluteOrStd f
406 fixUrl :: [DarcsFlag] -> String -> IO String
407 fixUrl opts f = if is_file f
408 then toFilePath `fmap` fixFilePath opts f
409 else return f
411 fixSubPaths :: [DarcsFlag] -> [FilePath] -> IO [SubPath]
412 fixSubPaths flags fs =
413 withCurrentDirectory o $
414 do fixedfs <- mapM fixit $ filter (not.null) fs
415 let (good, bad) = partitionEither fixedfs
416 unless (null bad) $
417 putStrLn $ "Ignoring non-repository paths: " ++ unwords bad
418 return $ nub good
419 where
420 (r,o) = case extract_fix_path flags of
421 Just xxx -> xxx
422 Nothing -> bug "Can't fix path in fixSubPaths"
423 fixit p = do ap <- ioAbsolute p
424 case makeSubPathOf r ap of
425 Just sp -> return $ Right sp
426 Nothing -> return $ maybe (Left p) Right $ simpleSubPath p
428 partitionEither :: [Either a b] -> ([b],[a])
429 partitionEither es = ( [b | Right b <- es]
430 , [a | Left a <- es] )
432 -- as opposed to just '.'
433 areFileArgs :: [SubPath] -> Bool
434 areFileArgs rps = concatMap toFilePath rps /= ""
435 \end{code}
437 \begin{code}
438 -- | 'list_option' is an option which lists the command's arguments
439 list_options :: DarcsOption
440 list_options = DarcsNoArgOption [] ["list-options"] ListOptions
441 "simply list the command's arguments"
443 flagToString :: [DarcsOption] -> DarcsFlag -> Maybe String
444 flagToString x f = maybeHead $ catMaybes $ map f2o x
445 where f2o (DarcsArgOption _ (s:_) c _ _) = do arg <- get_content f
446 if c arg == f
447 then return $ unwords [('-':'-':s), arg]
448 else Nothing
449 f2o (DarcsNoArgOption _ (s:_) f' _) | f == f' = Just ('-':'-':s)
450 f2o (DarcsMultipleChoiceOption xs) = maybeHead $ catMaybes $ map f2o xs
451 f2o _ = Nothing
452 maybeHead (a:_) = Just a
453 maybeHead [] = Nothing
455 reponame :: DarcsOption
456 tagname :: DarcsOption
457 deps_sel :: DarcsOption
458 checkpoint :: DarcsOption
459 partial :: DarcsOption
460 partial_check :: DarcsOption
461 tokens :: DarcsOption
462 working_repo_dir :: DarcsOption
463 possibly_remote_repo_dir :: DarcsOption
464 disable :: DarcsOption
465 restrict_paths :: DarcsOption
467 pipe_interactive, all_pipe_interactive, all_interactive, all_patches, interactive, pipe,
468 human_readable, diffflags, allow_problematic_filenames, noskip_boring,
469 ask_long_comment, match_one_nontag, changes_reverse, creatorhash,
470 changes_format, match_one_context, happy_forwarding, send_to_context,
471 diff_cmd_flag, store_in_memory, use_external_merge,
472 pull_conflict_options, target, cc, apply_conflict_options, reply, xmloutput,
473 distname_option, patchname_option, edit_description,
474 output, output_auto_name, unidiff, repo_combinator,
475 unified, summary, uncompress_nocompress, subject,
476 nocompress, match_several_or_range, match_several_or_last,
477 author, askdeps, lookforadds, ignoretimes, test, notest, help, force_replace,
478 help_on_match, allow_unrelated_repos,
479 match_one, match_range, match_several, fancy_move_add, sendmail_cmd,
480 logfile, rmlogfile, leave_test_dir, from_opt, set_default, pristine_tree
482 :: DarcsOption
484 recursive :: String -> DarcsOption
486 sign, applyas, verify :: DarcsOption
487 \end{code}
489 \section{Common options to darcs commands}
491 \begin{options}
492 --help
493 \end{options}
494 Every \verb|COMMAND| accepts \verb!--help! as an argument, which tells it to
495 provide a bit of help. Among other things, this help always provides an
496 accurate listing of the options available with that command, and is
497 guaranteed never to be out of sync with the version of darcs you actually
498 have installed (unlike this manual, which could be for an entirely
499 different version of darcs).
500 \begin{verbatim}
501 % darcs COMMAND --help
502 \end{verbatim}
503 \begin{code}
504 help = DarcsNoArgOption ['h'] ["help"] Help
505 "shows brief description of command and its arguments"
507 help_on_match = DarcsNoArgOption [] ["match"] HelpOnMatch
508 "shows a summary of how to use patch matching rules"
509 \end{code}
511 \begin{options}
512 --disable
513 \end{options}
514 Every {\tt COMMAND} accepts the \verb!--disable! option, which can be used in
515 \verb!_darcs/prefs/defaults! to disable some commands in the repository. This
516 can be helpful if you want to protect the repository from accidental use of
517 advanced commands like obliterate, unpull, unrecord or amend-record.
518 \begin{code}
519 disable = DarcsNoArgOption [] ["disable"] Disable
520 "disable this command"
521 \end{code}
523 \begin{options}
524 --verbose, --quiet, --normal-verbosity
525 \end{options}
526 Most commands also accept the \verb!--verbose! option, which tells darcs to
527 provide additional output. The amount of verbosity varies from command to
528 command. Commands that accept \verb!--verbose\verb! also accept \verb!--quiet\verb!,
529 which surpresses non-error output, and \verb!--normal-verbosity\verb! which can be
530 used to restore the default verbosity if \verb!--verbose! or \verb!--quiet! is in
531 the defaults file.
533 \begin{options}
534 --debug, --debug-http
535 \end{options}
536 Many commands also accept the \verb!--debug! option, which causes darcs to generate
537 additional output that may be useful for debugging its behavior, but which otherwise
538 would not be interesting. Option \verb!--debug-http! makes darcs output debugging
539 info for curl and libwww.
540 \begin{code}
541 any_verbosity :: [DarcsOption]
542 any_verbosity =[DarcsMultipleChoiceOption
543 [DarcsNoArgOption [] ["debug"] Debug
544 "give only debug output",
545 DarcsNoArgOption [] ["debug-verbose"] DebugVerbose
546 "give debug and verbose output",
547 DarcsNoArgOption [] ["debug-http"] DebugHTTP
548 "give debug output for curl and libwww",
549 DarcsNoArgOption ['v'] ["verbose"] Verbose
550 "give verbose output",
551 DarcsNoArgOption ['q'] ["quiet"] Quiet
552 "suppress informational output",
553 DarcsNoArgOption [] ["standard-verbosity"] NormalVerbosity
554 "neither verbose nor quiet output"],
555 DarcsNoArgOption [] ["timings"] Timings "provide debugging timings information"]
556 \end{code}
558 \begin{options}
559 --repodir
560 \end{options}
561 Another common option is the \verb!--repodir! option, which allows you to
562 specify the directory of the repository in which to perform the command.
563 This option is used with commands, such as whatsnew, that ordinarily would
564 be performed within a repository directory, and allows you to use those
565 commands without actually being in the repository directory when calling the
566 command. This is useful when running darcs in a pipe, as might be the case
567 when running \verb'apply' from a mailer.
569 \begin{code}
570 working_repo_dir = DarcsArgOption [] ["repodir"] WorkDir "DIRECTORY"
571 "specify the repository directory in which to run"
572 possibly_remote_repo_dir = DarcsArgOption [] ["repo"] RepoDir "URL"
573 "specify the repository URL"
574 get_repodir :: [DarcsFlag] -> String
575 get_repodir [] = "."
576 get_repodir (WorkDir r:_) = r
577 get_repodir (RepoDir r:_) = r
578 get_repodir (_:fs) = get_repodir fs
580 -- | 'get_repourl' takes a list of flags and returns the url of the
581 -- repository specified by @Repodir \"directory\"@ in that list of flags, if any.
582 -- This flag is present if darcs was invoked with @--repodir=DIRECTORY@
583 get_repourl :: [DarcsFlag] -> Maybe String
584 get_repourl [] = Nothing
585 get_repourl (RepoDir d:_) | not (is_file d) = Just d
586 get_repourl (_:fs) = get_repourl fs
587 \end{code}
589 \begin{options}
590 --remote-repo
591 \end{options}
593 Some commands, such as \verb'pull' require a remote repository to be specified,
594 either from the command line or as a default. The \verb!--remote-repo!
595 provides an alternative way to supply this remote repository path. This flag
596 can be seen as temporarily ``replacing'' the default repository. Setting it
597 causes the command to ignore the default repository (it also does not affect,
598 i.e. overwrite the default repository). On the other hand, if any other
599 repositories are supplied as command line arguments, this flag will be ignored
600 (and the default repository may be overwritten).
602 \begin{code}
603 -- | 'remote_repo' is the option used to specify the URL of the remote
604 -- repository to work with
605 remote_repo :: DarcsOption
606 remote_repo = DarcsArgOption [] ["remote-repo"] RemoteRepo "URL"
607 "specify the remote repository URL to work with"
609 -- | 'get_remote_repo' takes a list of flags and returns the url of the remote
610 -- repository specified by @RemoteRepo \"directory\"@ in that list of flags, if any.
611 get_remote_repo :: [DarcsFlag] -> Maybe String
612 get_remote_repo (RemoteRepo r : _) = Just r
613 get_remote_repo (_:fs) = get_remote_repo fs
614 get_remote_repo [] = Nothing
615 \end{code}
617 \input{Darcs/Match.lhs}
618 \input{Darcs/Patch/Match.lhs}
620 \begin{code}
621 patchname_option = DarcsArgOption ['m'] ["patch-name"] PatchName "PATCHNAME"
622 "name of patch"
624 send_to_context = DarcsAbsPathOption [] ["context"] Context "FILENAME"
625 "send to context stored in FILENAME"
627 match_one_context =
628 DarcsMultipleChoiceOption
629 [DarcsArgOption [] ["to-match"] mp "PATTERN"
630 "select changes up to a patch matching PATTERN",
631 DarcsArgOption [] ["to-patch"] OnePatch "REGEXP"
632 "select changes up to a patch matching REGEXP",
633 __tag,
634 DarcsAbsPathOption [] ["context"] Context "FILENAME"
635 "version specified by the context in FILENAME"
637 where mp s = OnePattern (patch_match s)
639 match_one = concat_options [__match, __patch, __tag, __index]
640 match_one_nontag = concat_options [__match, __patch, __index]
641 match_several = concat_options [__matches, __patches, __tags]
642 match_range = concat_options [match_to, match_from, __match, __patch, __last, __indexes]
643 match_several_or_range = concat_options [match_to, match_from, __last, __indexes,
644 __matches, __patches, __tags]
645 match_several_or_last = concat_options [match_from, __last, __matches, __patches, __tags]
647 match_to, match_from :: DarcsOption
648 match_to = DarcsMultipleChoiceOption
649 [DarcsArgOption [] ["to-match"] uptop "PATTERN"
650 "select changes up to a patch matching PATTERN",
651 DarcsArgOption [] ["to-patch"] UpToPatch "REGEXP"
652 "select changes up to a patch matching REGEXP",
653 DarcsArgOption [] ["to-tag"] UpToTag "REGEXP"
654 "select changes up to a tag matching REGEXP"]
655 where uptop s = UpToPattern (patch_match s)
656 match_from = DarcsMultipleChoiceOption
657 [DarcsArgOption [] ["from-match"] fromp "PATTERN"
658 "select changes starting with a patch matching PATTERN",
659 DarcsArgOption [] ["from-patch"] AfterPatch "REGEXP"
660 "select changes starting with a patch matching REGEXP",
661 DarcsArgOption [] ["from-tag"] AfterTag "REGEXP"
662 "select changes starting with a tag matching REGEXP"]
663 where fromp s = AfterPattern (patch_match s)
665 __tag, __tags, __patch, __patches, __match, __matches, __last, __index, __indexes :: DarcsOption
667 __tag = DarcsArgOption ['t'] ["tag"] OneTag "REGEXP"
668 "select tag matching REGEXP"
669 __tags = DarcsArgOption ['t'] ["tags"] OneTag "REGEXP"
670 "select tags matching REGEXP"
672 __patch = DarcsArgOption ['p'] ["patch"] OnePatch "REGEXP"
673 "select a single patch matching REGEXP"
674 __patches = DarcsArgOption ['p'] ["patches"] SeveralPatch "REGEXP"
675 "select patches matching REGEXP"
677 __match = DarcsArgOption [] ["match"] mp "PATTERN"
678 "select a single patch matching PATTERN"
679 where mp s = OnePattern (patch_match s)
680 __matches = DarcsArgOption [] ["matches"] mp "PATTERN"
681 "select patches matching PATTERN"
682 where mp s = SeveralPattern (patch_match s)
684 __last = DarcsArgOption [] ["last"] lastn "NUMBER"
685 "select the last NUMBER patches"
686 where lastn s = if and (map isDigit s)
687 then LastN (read s)
688 else LastN (-1)
690 __index = DarcsArgOption ['n'] ["index"] indexrange "N-M" "select a range of patches"
691 where indexrange s = if all isDigit s
692 then PatchIndexRange (read s) (read s)
693 else PatchIndexRange 0 0
695 __indexes = DarcsArgOption ['n'] ["index"] indexrange "N-M" "select a range of patches"
696 where indexrange s = if all isokay s
697 then if '-' `elem` s
698 then let x1 = takeWhile (/= '-') s
699 x2 = reverse $ takeWhile (/= '-') $ reverse s
700 in PatchIndexRange (read x1) (read x2)
701 else PatchIndexRange (read s) (read s)
702 else PatchIndexRange 0 0
703 isokay c = isDigit c || c == '-'
705 -- | 'get_context' takes a list of flags and returns the context
706 -- specified by @Context c@ in that list of flags, if any.
707 -- This flag is present if darcs was invoked with @--context=FILE@
708 get_context :: [DarcsFlag] -> Maybe AbsolutePath
709 get_context xs = listToMaybe [ c | Context c <- xs ]
710 \end{code}
712 \begin{code}
713 notest = DarcsMultipleChoiceOption
714 [DarcsNoArgOption [] ["no-test"] NoTest "don't run the test script",
715 DarcsNoArgOption [] ["test"] Test "run the test script"]
716 test = DarcsMultipleChoiceOption
717 [DarcsNoArgOption [] ["test"] Test "run the test script",
718 DarcsNoArgOption [] ["no-test"] NoTest "don't run the test script"]
719 leave_test_dir = DarcsMultipleChoiceOption
720 [DarcsNoArgOption [] ["leave-test-directory"]
721 LeaveTestDir "don't remove the test directory",
722 DarcsNoArgOption [] ["remove-test-directory"]
723 NoLeaveTestDir "remove the test directory"]
724 \end{code}
726 \begin{options}
727 --ignore-times
728 \end{options}
729 Darcs optimizes its operations by keeping track of the modification times
730 of your files. This dramatically speeds up commands such as
731 \verb!whatsnew! and \verb!record! which would otherwise require reading
732 every file in the repository and comparing it with a reference version. However,
733 there are times when this can cause problems, such as when running a series
734 of darcs commands from a script, in which case often a file will be
735 modified twice in the same second, which can lead to the second
736 modification going unnoticed. The solution to such predicaments is the
737 \verb!--ignore-times! option, which instructs darcs not to trust the file
738 modification times, but instead to check each file's contents explicitly.
739 \begin{code}
740 ignoretimes = DarcsNoArgOption [] ["ignore-times"] IgnoreTimes
741 "don't trust the file modification times"
742 lookforadds =
743 DarcsMultipleChoiceOption
744 [DarcsNoArgOption ['l'] ["look-for-adds"] LookForAdds
745 "look for (non-boring) files that could be added",
746 DarcsNoArgOption [] ["dont-look-for-adds"] NoLookForAdds
747 "don't look for any files that could be added [DEFAULT]"]
749 fancy_move_add =
750 DarcsMultipleChoiceOption
751 [DarcsNoArgOption [] ["date-trick"] FancyMoveAdd
752 "add files with date appended to avoid conflict [EXPERIMENTAL] ",
753 DarcsNoArgOption [] ["no-date-trick"] NoFancyMoveAdd
754 "don't use experimental date appending trick [DEFAULT]"]
756 pristine_tree =
757 DarcsMultipleChoiceOption
758 [DarcsNoArgOption [] ["plain-pristine-tree"] PristinePlain
759 "use a plain pristine tree [DEFAULT]",
760 DarcsNoArgOption [] ["no-pristine-tree"] PristineNone
761 "use no pristine tree"]
763 \end{code}
765 \begin{code}
766 askdeps =
767 DarcsMultipleChoiceOption
768 [DarcsNoArgOption [] ["ask-deps"] AskDeps
769 "ask for extra dependencies",
770 DarcsNoArgOption [] ["no-ask-deps"] NoAskDeps
771 "don't ask for extra dependencies"]
773 ask_long_comment =
774 DarcsMultipleChoiceOption
775 [DarcsNoArgOption [] ["edit-long-comment"] EditLongComment
776 "edit the long comment by default",
777 DarcsNoArgOption [] ["skip-long-comment"] NoEditLongComment
778 "don't give a long comment",
779 DarcsNoArgOption [] ["prompt-long-comment"] PromptLongComment
780 "prompt for whether to edit the long comment"]
781 \end{code}
783 \begin{options}
784 --author
785 \end{options}
786 \label{env:DARCS_EMAIL}
787 Several commands need to be able to identify you. Conventionally, you
788 provide an email address for this purpose, which can include comments,
789 e.g.\ \verb!David Roundy <droundy@abridgegame.org>!. The easiest way to do
790 this is
791 to define an environment variable \verb!EMAIL! or \verb!DARCS_EMAIL! (with
792 the latter overriding the former). You can also override this using the
793 \verb!--author! flag to any command. Alternatively, you could set your
794 email address on a per-repository basis using the ``defaults'' mechanism
795 for ``ALL'' commands, as described in Appendix~\ref{repository_format}.
796 Or, you could specify the author on a per-repository basis using the
797 \verb!_darcs/prefs/author! file as described in section~\ref{author_prefs}.
799 Also, a global author file can be created in your home directory with the name
800 \verb!.darcs/author!. This file overrides the
801 contents of the environment variables, but a repository-specific author
802 file overrides the global author file.
804 \begin{code}
805 logfile = DarcsAbsPathOption [] ["logfile"] LogFile "FILE"
806 "give patch name and comment in file"
808 rmlogfile = DarcsNoArgOption [] ["delete-logfile"] RmLogFile
809 "delete the logfile when done"
811 author = DarcsArgOption ['A'] ["author"] Author "EMAIL" "specify author id"
812 from_opt = DarcsArgOption [] ["from"] Author "EMAIL" "specify email address"
814 -- | 'get_author' takes a list of flags and returns the author of the
815 -- change specified by @Author \"Leo Tolstoy\"@ in that list of flags, if any.
816 -- Otherwise, if @Pipe@ is present, asks the user who is the author and
817 -- returns the answer. If neither are present, try to guess the author,
818 -- from @_darcs/prefs@, and if it's not possible, ask the user.
819 get_author :: [DarcsFlag] -> IO String
820 get_author (Author a:_) = return a
821 get_author (Pipe:_) = do askUser "Who is the author? "
822 get_author (_:flags) = get_author flags
823 get_author [] = do
824 easy_author <- get_easy_author
825 case easy_author of
826 Just a -> return a
827 Nothing -> do
828 aminrepo <- doesDirectoryExist (darcsdir++"/prefs")
829 if aminrepo then do
830 putStr "Darcs needs to know what name (conventionally an email "
831 putStr "address) to use as the\npatch author, e.g. 'Fred Bloggs "
832 putStr "<fred@bloggs.invalid>'. If you provide one\nnow "
833 putStr ("it will be stored in the file '"++darcsdir++"/prefs/author' and ")
834 putStr "used as a default\nin the future. To change your preferred "
835 putStr "author address, simply delete or edit\nthis file.\n\n"
836 add <- askUser "What is your email address? "
837 writeFile (darcsdir++"/prefs/author") add
838 return add
839 else do askUser "What is your email address (e.g. John Doe <a@b.com>)? "
841 -- | 'get_easy_author' tries to get the author name first from the repository preferences,
842 -- then from global preferences, then from environment variables. Returns 'Nothing' if it
843 -- could not get it.
844 get_easy_author :: IO (Maybe String)
845 get_easy_author = firstJustIO [ firstNotBlank `fmap` get_preflist "author",
846 firstNotBlank `fmap` get_global "author",
847 maybeGetEnv "DARCS_EMAIL",
848 maybeGetEnv "EMAIL" ]
849 \end{code}
851 \begin{options}
852 --dont-compress, --compress
853 \end{options}
854 By default, darcs commands that write patches to disk will compress the
855 patch files. If you don't want this, you can choose the
856 \verb!--dont-compress! option, which causes darcs not to compress the patch
857 file.
859 \begin{code}
860 nocompress = concat_options [__compress, __dont_compress]
861 uncompress_nocompress = concat_options [__compress, __dont_compress, __uncompress]
863 __compress, __dont_compress, __uncompress :: DarcsOption
864 __compress = DarcsNoArgOption [] ["compress"] Compress
865 "create compressed patches"
866 __dont_compress = DarcsNoArgOption [] ["dont-compress"] NoCompress
867 "don't create compressed patches"
868 __uncompress = DarcsNoArgOption [] ["uncompress"] UnCompress
869 "uncompress patches"
870 \end{code}
872 \begin{code}
873 summary = DarcsMultipleChoiceOption
874 [DarcsNoArgOption ['s'] ["summary"] Summary "summarize changes",
875 DarcsNoArgOption [] ["no-summary"] NoSummary "don't summarize changes"]
876 unified = DarcsNoArgOption ['u'] ["unified"] Unified
877 "output patch in a darcs-specific format similar to diff -u"
878 unidiff = DarcsNoArgOption ['u'] ["unified"] Unified
879 "pass -u option to diff"
880 diff_cmd_flag = DarcsArgOption [] ["diff-command"]
881 DiffCmd "COMMAND" "specify diff command (ignores --diff-opts)"
882 store_in_memory = DarcsNoArgOption [] ["store-in-memory"] StoreInMemory
883 "do patch application in memory rather than on disk"
884 \end{code}
886 \begin{code}
887 target = DarcsArgOption [] ["to"] Target "EMAIL" "specify destination email"
888 cc = DarcsArgOption [] ["cc"] Cc "EMAIL" "mail results to additional EMAIL(s). Requires --reply"
890 -- |'get_cc' takes a list of flags and returns the addresses to send a copy of
891 -- the patch bundle to when using @darcs send@.
892 -- looks for a cc address specified by @Cc \"address\"@ in that list of flags.
893 -- Returns the addresses as a comma separated string.
894 get_cc :: [DarcsFlag] -> String
895 get_cc fs = lt $ catMaybes $ map whatcc fs
896 where whatcc (Cc t) = Just t
897 whatcc _ = Nothing
898 lt [t] = t
899 lt [t,""] = t
900 lt (t:ts) = t++" , "++lt ts
901 lt [] = ""
902 \end{code}
904 \begin{code}
905 subject = DarcsArgOption [] ["subject"] Subject "SUBJECT" "specify mail subject"
907 -- |'get_subject' takes a list of flags and returns the subject of the mail
908 -- to be sent by @darcs send@. Looks for a subject specified by
909 -- @Subject \"subject\"@ in that list of flags, if any.
910 -- This flag is present if darcs was invoked with @--subject=SUBJECT@
911 get_subject :: [DarcsFlag] -> Maybe String
912 get_subject (Subject s:_) = Just s
913 get_subject (_:fs) = get_subject fs
914 get_subject [] = Nothing
915 \end{code}
917 \begin{code}
918 output = DarcsAbsPathOrStdOption ['o'] ["output"] Output "FILE"
919 "specify output filename"
920 \end{code}
922 \begin{code}
923 output_auto_name = DarcsOptAbsPathOption ['O'] ["output-auto-name"] "." OutputAutoName "DIRECTORY"
924 "output to automatically named file in DIRECTORY, default: current directory"
925 \end{code}
927 \begin{code}
928 edit_description =
929 DarcsMultipleChoiceOption
930 [DarcsNoArgOption [] ["edit-description"] EditDescription
931 "edit the patch bundle description",
932 DarcsNoArgOption [] ["dont-edit-description"] NoEditDescription
933 "don't edit the patch bundle description"]
934 \end{code}
936 \begin{code}
937 distname_option = DarcsArgOption ['d'] ["dist-name"] DistName "DISTNAME"
938 "name of version"
939 \end{code}
941 \begin{code}
942 recursive h
943 = DarcsMultipleChoiceOption
944 [DarcsNoArgOption ['r'] ["recursive"] Recursive h,
945 DarcsNoArgOption [] ["not-recursive"] NoRecursive ("don't "++h)]
946 \end{code}
948 \begin{code}
949 inventory_choices :: DarcsOption
950 inventory_choices =
951 DarcsMultipleChoiceOption
952 [DarcsNoArgOption [] ["hashed"] UseHashedInventory
953 "Some new features. Compatible with older repos",
954 DarcsNoArgOption [] ["darcs-2"] UseFormat2
955 "All features. Related repos must use same format [DEFAULT]",
956 DarcsNoArgOption [] ["old-fashioned-inventory"] UseOldFashionedInventory
957 "Minimal features. What older repos use."]
959 get_inventory_choices :: DarcsOption
960 get_inventory_choices =
961 DarcsMultipleChoiceOption
962 [DarcsNoArgOption [] ["hashed"] UseHashedInventory
963 "Convert darcs-1 format to hashed format",
964 DarcsNoArgOption [] ["old-fashioned-inventory"] UseOldFashionedInventory
965 "Convert from hashed to darcs-1 format"]
966 \end{code}
968 \begin{code}
969 xmloutput = DarcsNoArgOption [] ["xml-output"] XMLOutput
970 "generate XML formatted output"
971 \end{code}
973 \begin{code}
974 creatorhash = DarcsArgOption [] ["creator-hash"] CreatorHash "HASH"
975 "specify hash of creator patch (see docs)"
976 \end{code}
978 \begin{code}
979 sign = DarcsMultipleChoiceOption
980 [DarcsNoArgOption [] ["sign"] Sign
981 "sign the patch with your gpg key",
982 DarcsArgOption [] ["sign-as"] SignAs "KEYID"
983 "sign the patch with a given keyid",
984 DarcsArgOption [] ["sign-ssl"] SignSSL "IDFILE"
985 "sign the patch using openssl with a given private key",
986 DarcsNoArgOption [] ["dont-sign"] NoSign
987 "don't sign the patch"]
988 applyas = DarcsMultipleChoiceOption
989 [DarcsArgOption [] ["apply-as"] ApplyAs "USERNAME"
990 "apply patch as another user using sudo",
991 DarcsNoArgOption [] ["apply-as-myself"] NonApply
992 "don't use sudo to apply as another user [DEFAULT]"]
993 happy_forwarding = DarcsNoArgOption [] ["happy-forwarding"] HappyForwarding
994 "forward unsigned messages without extra header"
995 set_default = DarcsMultipleChoiceOption
996 [DarcsNoArgOption [] ["set-default"] SetDefault
997 "set default repository [DEFAULT]",
998 DarcsNoArgOption [] ["no-set-default"] NoSetDefault
999 "don't set default repository"]
1000 \end{code}
1002 \begin{code}
1003 verify = DarcsMultipleChoiceOption
1004 [DarcsAbsPathOption [] ["verify"] Verify "PUBRING"
1005 "verify that the patch was signed by a key in PUBRING",
1006 DarcsAbsPathOption [] ["verify-ssl"] VerifySSL "KEYS"
1007 "verify using openSSL with authorized keys from file KEYS",
1008 DarcsNoArgOption [] ["no-verify"] NonVerify
1009 "don't verify patch signature"]
1010 \end{code}
1012 \begin{code}
1013 reponame = DarcsArgOption [] ["repo-name"] WorkDir "DIRECTORY"
1014 "path of output directory"
1015 tagname = DarcsArgOption ['t'] ["tag"] TagName "TAGNAME"
1016 "name of version to checkpoint"
1017 deps_sel = DarcsMultipleChoiceOption
1018 [DarcsNoArgOption [] ["no-deps"] DontGrabDeps
1019 "don't automatically fulfill dependencies",
1020 DarcsNoArgOption [] ["dont-prompt-for-dependencies"] DontPromptForDependencies
1021 "don't ask about patches that are depended on by matched patches (with --match or --patch)",
1022 DarcsNoArgOption [] ["prompt-for-dependencies"] PromptForDependencies
1023 "prompt about patches that are depended on by matched patches [DEFAULT]"]
1024 checkpoint = DarcsNoArgOption [] ["checkpoint"] CheckPoint
1025 "create a checkpoint file (see get --partial)"
1026 tokens = DarcsArgOption [] ["token-chars"] Toks "\"[CHARS]\""
1027 "define token to contain these characters"
1029 partial = concat_options [__partial, __lazy, __ephemeral, __complete]
1030 partial_check = concat_options [__complete, __partial]
1032 __partial, __lazy, __ephemeral, __complete :: DarcsOption
1033 __partial = DarcsNoArgOption [] ["partial"] Partial
1034 "get partial repository using checkpoint (old-fashioned format only)"
1035 __lazy = DarcsNoArgOption [] ["lazy"] Lazy
1036 "get patch files only as needed"
1037 __ephemeral = DarcsNoArgOption [] ["ephemeral"] Ephemeral
1038 "don't save patch files in the repository"
1039 __complete = DarcsNoArgOption [] ["complete"] Complete
1040 "get a complete copy of the repository"
1041 \end{code}
1043 \begin{code}
1044 force_replace = DarcsMultipleChoiceOption
1045 [DarcsNoArgOption ['f'] ["force"] ForceReplace
1046 "proceed with replace even if 'new' token already exists",
1047 DarcsNoArgOption [] ["no-force"]
1048 NonForce "don't force the replace if it looks scary"]
1049 \end{code}
1051 \begin{code}
1052 reply = DarcsArgOption [] ["reply"] Reply "FROM" "reply to email-based patch using FROM address"
1053 apply_conflict_options
1054 = DarcsMultipleChoiceOption
1055 [DarcsNoArgOption [] ["mark-conflicts"]
1056 MarkConflicts "mark conflicts",
1057 DarcsNoArgOption [] ["allow-conflicts"]
1058 AllowConflicts "allow conflicts, but don't mark them",
1059 DarcsNoArgOption [] ["no-resolve-conflicts"] NoAllowConflicts
1060 "equivalent to --dont-allow-conflicts, for backwards compatibility",
1061 DarcsNoArgOption [] ["dont-allow-conflicts"]
1062 NoAllowConflicts "fail on patches that create conflicts [DEFAULT]"]
1063 pull_conflict_options
1064 = DarcsMultipleChoiceOption
1065 [DarcsNoArgOption [] ["mark-conflicts"]
1066 MarkConflicts "mark conflicts [DEFAULT]",
1067 DarcsNoArgOption [] ["allow-conflicts"]
1068 AllowConflicts "allow conflicts, but don't mark them",
1069 DarcsNoArgOption [] ["dont-allow-conflicts"]
1070 NoAllowConflicts "fail on patches that create conflicts"]
1071 use_external_merge = DarcsArgOption [] ["external-merge"]
1072 ExternalMerge "COMMAND" "use external tool to merge conflicts"
1073 \end{code}
1075 \begin{options}
1076 --dry-run
1077 \end{options}
1078 The \verb!--dry-run! option will cause darcs not to actually take the specified
1079 action, but only print what would have happened. Not all commands accept
1080 \verb!--dry-run!, but those that do should accept the \verb!--summary! option.
1082 \begin{options}
1083 --summary, --no-summary
1084 \end{options}
1085 The \verb!--summary! option shows a summary of the patches that would have been
1086 pulled/pushed/whatever. The format is similar to the output format of
1087 \verb!cvs update! and looks like this:
1089 \begin{verbatim}
1090 A ./added_but_not_recorded.c
1091 A! ./added_but_not_recorded_conflicts.c
1092 a ./would_be_added_if_look_for_adds_option_was_used.h
1094 M ./modified.t -1 +1
1095 M! ./modified_conflicts.t -1 +1
1097 R ./removed_but_not_recorded.c
1098 R! ./removed_but_not_recorded_conflicts.c
1100 \end{verbatim}
1102 You can probably guess what the flags mean from the clever file names.
1103 \begin{description}
1104 \item{\texttt{A}} is for files that have been added but not recorded yet.
1105 \item{\texttt{a}} is for files found using the \verb!--look-for-adds! option available for
1106 \verb!whatsnew! and \verb!record!. They have not been added yet, but would be
1107 added automatically if \verb!--look-for-adds! were used with the next
1108 \verb!record! command.
1110 \item{\texttt{M}} is for files that have been modified in the working directory but not
1111 recorded yet. The number of added and subtracted lines is also shown.
1113 \item{\texttt{R}} is for files that have been removed, but the removal is not
1114 recorded yet.
1115 \end{description}
1116 An exclamation mark appears next to any option that has a conflict.
1118 \begin{code}
1119 -- NOTE: I'd rather work to have no uses of dry_run_noxml, so that any time
1120 -- --dry-run is a possibility, automated users can examine the results more
1121 -- easily with --xml.
1122 dry_run_noxml :: DarcsOption
1123 dry_run_noxml = DarcsNoArgOption [] ["dry-run"] DryRun
1124 "don't actually take the action"
1126 dry_run :: [DarcsOption]
1127 dry_run = [dry_run_noxml, xmloutput]
1129 -- | @'showFriendly' flags patch@ returns a 'Doc' representing the right
1130 -- way to show @patch@ given the list @flags@ of flags darcs was invoked with.
1131 showFriendly :: Patchy p => [DarcsFlag] -> p C(x y) -> Doc
1132 showFriendly opts p = if Verbose `elem` opts
1133 then showNicely p
1134 else if Summary `elem` opts
1135 then Darcs.Patch.summary p
1136 else description p
1138 -- | @'print_dry_run_message_and_exit' action opts patches@ prints a string
1139 -- representing the action that would be taken if the @--dry-run@ option
1140 -- had not been passed to darcs. Then darcs exits successfully.
1141 -- @action@ is the name of the action being taken, like @\"push\"@
1142 -- @opts@ is the list of flags which were sent to darcs
1143 -- @patches@ is the sequence of patches which would be touched by @action@.
1144 print_dry_run_message_and_exit :: RepoPatch p => String -> [DarcsFlag] -> FL (PatchInfoAnd p) C(x y) -> IO ()
1145 print_dry_run_message_and_exit action opts patches =
1146 do when (DryRun `elem` opts) $ do
1147 putInfo $ text $ "Would " ++ action ++ " the following changes:"
1148 putDocLn $ put_mode
1149 putInfo $ text $ ""
1150 putInfo $ text $ "Making no changes: this is a dry run."
1151 exitWith ExitSuccess
1152 when (All `elem` opts && Summary `elem` opts) $ do
1153 putInfo $ text $ "Will " ++ action ++ " the following changes:"
1154 putDocLn $ put_mode
1155 where put_mode = if XMLOutput `elem` opts
1156 then (text "<patches>" $$
1157 vcat (mapFL (to_xml . info) patches) $$
1158 text "</patches>")
1159 else (vsep $ mapFL (showFriendly opts) patches)
1160 putInfo = if XMLOutput `elem` opts then \_ -> return () else putDocLn
1162 \end{code}
1164 \input{Darcs/Resolution.lhs}
1166 \begin{code}
1167 noskip_boring = DarcsNoArgOption [] ["boring"]
1168 Boring "don't skip boring files"
1169 allow_problematic_filenames = DarcsMultipleChoiceOption
1170 [DarcsNoArgOption [] ["case-ok"] AllowCaseOnly
1171 "don't refuse to add files differing only in case"
1172 ,DarcsNoArgOption [] ["reserved-ok"] AllowWindowsReserved
1173 "don't refuse to add files with Windows-reserved names"
1175 diffflags = DarcsArgOption [] ["diff-opts"]
1176 DiffFlags "OPTIONS" "options to pass to diff"
1177 \end{code}
1179 \begin{code}
1180 changes_format = DarcsMultipleChoiceOption
1181 [DarcsNoArgOption [] ["context"]
1182 (Context rootDirectory) "give output suitable for get --context",
1183 xmloutput,
1184 human_readable,
1185 DarcsNoArgOption [] ["number"] NumberPatches "number the changes",
1186 DarcsNoArgOption [] ["count"] Count "output count of changes"
1188 changes_reverse = DarcsNoArgOption [] ["reverse"] Reverse
1189 "show changes in reverse order"
1191 only_to_files :: DarcsOption
1192 only_to_files = DarcsNoArgOption [] ["only-to-files"] OnlyChangesToFiles
1193 "show only changes to specified files"
1195 human_readable = DarcsNoArgOption [] ["human-readable"]
1196 HumanReadable "give human-readable output"
1197 pipe = DarcsNoArgOption [] ["pipe"] Pipe "ask user interactively for the patch metadata"
1199 interactive =
1200 DarcsNoArgOption ['i'] ["interactive"] Interactive
1201 "prompt user interactively"
1202 all_patches = DarcsNoArgOption ['a'] ["all"] All "answer yes to all patches"
1204 all_interactive = DarcsMultipleChoiceOption [all_patches, interactive]
1206 all_pipe_interactive
1207 = DarcsMultipleChoiceOption [all_patches,pipe,interactive]
1209 pipe_interactive =
1210 DarcsMultipleChoiceOption [pipe, interactive]
1212 repo_combinator =
1213 DarcsMultipleChoiceOption
1214 [DarcsNoArgOption [] ["intersection"] Intersection
1215 "take intersection of all repositories",
1216 DarcsNoArgOption [] ["union"] Union
1217 "take union of all repositories [DEFAULT]",
1218 DarcsNoArgOption [] ["complement"] Complement
1219 "take complement of repositories (in order listed)"]
1220 \end{code}
1222 \begin{code}
1223 -- | 'list_files' returns the list of all non-boring files in the repository
1224 list_files :: IO [String]
1225 list_files = do s <- slurp_all_but_darcs "."
1226 skip_boring <- boring_file_filter
1227 return (map drop_dotslash $ skip_boring $ list_slurpy s)
1229 drop_dotslash :: String -> String
1230 drop_dotslash ('.':'/':x) = drop_dotslash x
1231 drop_dotslash x = x
1233 -- | 'list_unregistered_files' returns the list of all non-boring unregistered
1234 -- files in the repository.
1235 list_unregistered_files :: IO [String]
1236 list_unregistered_files = withRepository [] $- \repository ->
1237 do s <- slurp_all_but_darcs "."
1238 skip_boring <- boring_file_filter
1239 regs <- slurp_pending repository
1240 return $ map drop_dotslash $ (skip_boring $ list_slurpy s) \\ (list_slurpy regs)
1242 -- | 'list_registered_files' returns the list of all registered files in the repository.
1243 list_registered_files :: IO [String]
1244 list_registered_files =
1245 (map drop_dotslash . list_slurpy) `fmap` (withRepository [] slurp_pending)
1246 \end{code}
1248 \begin{code}
1249 options_latex :: [DarcsOption] -> String
1250 options_latex opts = "\\begin{tabular}{lll}\n"++
1251 unlines (map option_latex opts)++
1252 "\\end{tabular}\n"
1254 latex_help :: String -> String
1255 latex_help h
1256 = "\\begin{minipage}{7cm}\n\\raggedright\n" ++ h ++ "\\end{minipage}\n"
1258 option_latex :: DarcsOption -> String
1259 option_latex (DarcsNoArgOption a b _ h) =
1260 show_short_options a ++ show_long_options b ++ latex_help h ++ "\\\\"
1261 option_latex (DarcsArgOption a b _ arg h) =
1262 show_short_options a ++
1263 show_long_options (map (++(" "++arg)) b) ++ latex_help h ++ "\\\\"
1264 option_latex (DarcsAbsPathOrStdOption a b _ arg h) =
1265 show_short_options a ++
1266 show_long_options (map (++(" "++arg)) b) ++ latex_help h ++ "\\\\"
1267 option_latex (DarcsAbsPathOption a b _ arg h) =
1268 show_short_options a ++
1269 show_long_options (map (++(" "++arg)) b) ++ latex_help h ++ "\\\\"
1270 option_latex (DarcsOptAbsPathOption a b _ _ arg h) =
1271 show_short_options a ++
1272 show_long_options (map (++("[="++arg++"]")) b) ++ latex_help h ++ "\\\\"
1273 option_latex (DarcsMultipleChoiceOption os) =
1274 unlines (map option_latex os)
1276 show_short_options :: [Char] -> String
1277 show_short_options [] = "&"
1278 show_short_options [c] = "\\verb!-"++[c]++"! &"
1279 show_short_options (c:cs) = "\\verb!-"++[c]++"!,"++show_short_options cs
1281 show_long_options :: [String] -> String
1282 show_long_options [] = " &"
1283 show_long_options [s] = "\\verb!--" ++ s ++ "! &"
1284 show_long_options (s:ss)
1285 = "\\verb!--" ++ s ++ "!,"++ show_long_options ss
1287 set_scripts_executable :: DarcsOption
1288 set_scripts_executable = DarcsMultipleChoiceOption
1289 [DarcsNoArgOption [] ["set-scripts-executable"] SetScriptsExecutable
1290 "make scripts executable",
1291 DarcsNoArgOption [] ["dont-set-scripts-executable"] DontSetScriptsExecutable
1292 "don't make scripts executable"]
1294 \end{code}
1296 \begin{code}
1297 relink, relink_pristine, sibling :: DarcsOption
1298 relink = DarcsNoArgOption [] ["relink"] Relink
1299 "relink random internal data to a sibling"
1301 relink_pristine = DarcsNoArgOption [] ["relink-pristine"] RelinkPristine
1302 "relink pristine tree (not recommended)"
1304 sibling = DarcsAbsPathOption [] ["sibling"] Sibling "URL"
1305 "specify a sibling directory"
1307 -- | 'flagsToSiblings' collects the contents of all @Sibling@ flags in a list of flags.
1308 flagsToSiblings :: [DarcsFlag] -> [AbsolutePath]
1309 flagsToSiblings ((Sibling s) : l) = s : (flagsToSiblings l)
1310 flagsToSiblings (_ : l) = flagsToSiblings l
1311 flagsToSiblings [] = []
1312 \end{code}
1314 \begin{code}
1315 nolinks :: DarcsOption
1316 nolinks = DarcsNoArgOption [] ["nolinks"] NoLinks
1317 "do not link repository or pristine to sibling"
1318 \end{code}
1320 \begin{code}
1321 reorder_patches :: DarcsOption
1322 reorder_patches = DarcsNoArgOption [] ["reorder-patches"] Reorder
1323 "reorder the patches in the repository"
1324 \end{code}
1325 \begin{options}
1326 --sendmail-command
1327 \end{options}
1329 \label{env:SENDMAIL}
1331 Several commands send email. The user can determine which mta to
1332 use with the \verb!--sendmail-command! switch. For repetitive usage
1333 of a specific sendmail command it is also possible to set the
1334 environment variable \verb!SENDMAIL!. If there is no command line
1335 switch given \verb!SENDMAIL! will be used if present.
1337 \begin{code}
1338 sendmail_cmd = DarcsArgOption [] ["sendmail-command"] SendmailCmd "COMMAND" "specify sendmail command"
1340 -- |'get_sendmail_cmd' takes a list of flags and returns the sendmail command
1341 -- to be used by @darcs send@. Looks for a command specified by
1342 -- @SendmailCmd \"command\"@ in that list of flags, if any.
1343 -- This flag is present if darcs was invoked with @--sendmail-command=COMMAND@
1344 -- Alternatively the user can set @$SENDMAIL@ which will be used as a fallback if present.
1345 get_sendmail_cmd :: [DarcsFlag] -> IO String
1346 get_sendmail_cmd (SendmailCmd a:_) = return a
1347 get_sendmail_cmd (_:flags) = get_sendmail_cmd flags
1348 get_sendmail_cmd [] = do easy_sendmail <- firstJustIO [ maybeGetEnv "SENDMAIL" ]
1349 case easy_sendmail of
1350 Just a -> return a
1351 Nothing -> return ""
1352 \end{code}
1354 \begin{code}
1355 files :: DarcsOption
1356 files = DarcsMultipleChoiceOption
1357 [DarcsNoArgOption [] ["files"] Files
1358 "include files in output [DEFAULT]",
1359 DarcsNoArgOption [] ["no-files"] NoFiles
1360 "don't include files in output"]
1362 directories :: DarcsOption
1363 directories = DarcsMultipleChoiceOption
1364 [DarcsNoArgOption [] ["directories"] Directories
1365 "include directories in output [DEFAULT]",
1366 DarcsNoArgOption [] ["no-directories"] NoDirectories
1367 "don't include directories in output"]
1369 pending :: DarcsOption
1370 pending = DarcsMultipleChoiceOption
1371 [DarcsNoArgOption [] ["pending"] Pending
1372 "reflect pending patches in output [DEFAULT]",
1373 DarcsNoArgOption [] ["no-pending"] NoPending
1374 "only included recorded patches in output"]
1376 nullFlag :: DarcsOption -- "null" is already taken
1377 nullFlag = DarcsNoArgOption ['0'] ["null"] NullFlag
1378 "separate file names by NUL characters"
1379 \end{code}
1380 \begin{options}
1381 --posthook=COMMAND, --no-posthook
1382 \end{options}
1383 To provide a command that should be run whenever a darcs command completes
1384 successfully, use \verb!--posthook! to specify the command. This is useful
1385 for people who want to have a command run whenever a patch is applied. Using
1386 \verb!--no-posthook! will disable running the command.
1387 \begin{options}
1388 --run-posthook, --prompt-posthook
1389 \end{options}
1390 These options control prompting before running the posthook. Use
1391 \verb!--prompt-posthook! to have darcs prompt before running the
1392 posthook command. You may use --run-posthook to reenable the default
1393 behavior of running user-specified posthooks.
1395 Some darcs commands export to the posthook command information about the
1396 changes being made. In particular, three environment variables are defined.
1397 \verb!DARCS_PATCHES! contains a human-readable summary of the patches being
1398 acted upon. The format is the same as "darcs changes". \verb!DARCS_PATCHES_XML!
1399 Contains the same details, in the same XML format as "darcs changes". Finally,
1400 \verb!DARCS_FILES! contains a list of the files affected, one file per line.
1401 If your repository has filenames including newlines, you'll just have to
1402 cope. Note, however, that \emph{none} of these environment variables are
1403 defined when running under windows. Note also that we refuse to pass
1404 environment variables greater in size than 10k, in order to avoid triggering
1405 \verb!E2BIG! errors.
1407 \begin{code}
1408 definePatches :: RepoPatch p => FL (PatchInfoAnd p) C(x y) -> IO ()
1409 #ifndef WIN32
1410 definePatches ps = do let k = "Defining environment variables"
1411 beginTedious k
1412 tediousSize k 3
1413 finishedOneIO k "DARCS_PATCHES"
1414 setEnvCautiously "DARCS_PATCHES" (renderString $ Darcs.Patch.summary ps)
1415 finishedOneIO k "DARCS_PATCHES_XML"
1416 setEnvCautiously "DARCS_PATCHES_XML"
1417 (renderString $ text "<patches>" $$
1418 vcat (mapFL (to_xml . info) ps) $$
1419 text "</patches>")
1420 finishedOneIO k "DARCS_FILES"
1421 setEnvCautiously "DARCS_FILES" (unlines$ list_touched_files ps)
1422 endTedious k
1424 setEnvCautiously :: String -> String -> IO ()
1425 setEnvCautiously e v | toobig (10*1024) v = return ()
1426 | otherwise = setEnv e v True
1427 where toobig :: Int -> [a] -> Bool
1428 toobig 0 _ = True
1429 toobig _ [] = False
1430 toobig n (_:xs) = toobig (n-1) xs
1431 #else
1432 definePatches _ = return ()
1433 #endif
1435 defineChanges :: Patchy p => p C(x y) -> IO ()
1436 #ifndef WIN32
1437 defineChanges ps = setEnvCautiously "DARCS_FILES" (unlines $ list_touched_files ps)
1438 #else
1439 defineChanges _ = return ()
1440 #endif
1442 posthook_cmd :: DarcsOption
1443 posthook_cmd = DarcsMultipleChoiceOption
1444 [DarcsArgOption [] ["posthook"] PosthookCmd
1445 "COMMAND" "specify command to run after this darcs command",
1446 DarcsNoArgOption [] ["no-posthook"] NoPosthook
1447 "don't run posthook command"]
1449 posthook_prompt :: DarcsOption
1450 posthook_prompt = DarcsMultipleChoiceOption
1451 [DarcsNoArgOption [] ["prompt-posthook"] AskPosthook
1452 "prompt before running posthook [DEFAULT]",
1453 DarcsNoArgOption [] ["run-posthook"] RunPosthook
1454 "run posthook command without prompting"]
1456 -- | 'get_posthook_cmd' takes a list of flags and returns the posthook command
1457 -- specified by @PosthookCmd a@ in that list of flags, if any.
1458 get_posthook_cmd :: [DarcsFlag] -> Maybe String
1459 get_posthook_cmd (PosthookCmd a:_) = Just a
1460 get_posthook_cmd (_:flags) = get_posthook_cmd flags
1461 get_posthook_cmd [] = Nothing
1462 \end{code}
1463 \begin{options}
1464 --prehook=COMMAND, --no-prehook
1465 \end{options}
1466 To provide a command that should be run before a darcs command is executed,
1467 use \verb!--prehook! to specify the command. An example use is
1468 for people who want to have a command run whenever a patch is to be recorded, such as
1469 translating line endings before recording patches. Using
1470 \verb!--no-prehook! will disable running the command.
1471 \begin{options}
1472 --run-prehook, --prompt-prehook
1473 \end{options
1474 These options control prompting before running the prehook. See the
1475 posthook documentation above for details.
1476 \begin{code}
1477 prehook_cmd :: DarcsOption
1478 prehook_cmd = DarcsMultipleChoiceOption
1479 [DarcsArgOption [] ["prehook"] PrehookCmd
1480 "COMMAND" "specify command to run before this darcs command",
1481 DarcsNoArgOption [] ["no-prehook"] NoPrehook
1482 "don't run prehook command"]
1484 prehook_prompt :: DarcsOption
1485 prehook_prompt = DarcsMultipleChoiceOption
1486 [DarcsNoArgOption [] ["prompt-prehook"] AskPrehook
1487 "prompt before running prehook [DEFAULT]",
1488 DarcsNoArgOption [] ["run-prehook"] RunPrehook
1489 "run prehook command without prompting"]
1491 -- | 'get_prehook_cmd' takes a list of flags and returns the prehook command
1492 -- specified by @PrehookCmd a@ in that list of flags, if any.
1493 get_prehook_cmd :: [DarcsFlag] -> Maybe String
1494 get_prehook_cmd (PrehookCmd a:_) = Just a
1495 get_prehook_cmd (_:flags) = get_prehook_cmd flags
1496 get_prehook_cmd [] = Nothing
1497 \end{code}
1499 \begin{options}
1500 --ssh-cm, --no-ssh-cm
1501 \end{options}
1503 For commands which invoke ssh, darcs will normally multiplex ssh
1504 sessions over a single connection as long as your version of ssh has
1505 the ControlMaster feature from OpenSSH versions 3.9 and above. This
1506 option will avoid darcs trying to use this feature even if your ssh
1507 supports it.
1509 \begin{options}
1510 --http-pipelining, --no-http-pipelining
1511 \end{options}
1513 When compiled with libwww or curl (version 7.18.0 and above), darcs can
1514 use HTTP pipelining. It is enabled by default for libwww and curl
1515 (version 7.19.1 and above). This option will make darcs enable or
1516 disable HTTP pipelining, overwriting default. Note that if HTTP
1517 pipelining is really used depends on the server.
1519 \begin{options}
1520 --no-cache
1521 \end{options}
1523 Do not use patch caches.
1524 \begin{code}
1525 network_options :: [DarcsOption]
1526 network_options =
1527 [DarcsMultipleChoiceOption
1528 [DarcsNoArgOption [] ["ssh-cm"] SSHControlMaster
1529 "use SSH ControlMaster feature",
1530 DarcsNoArgOption [] ["no-ssh-cm"] NoSSHControlMaster
1531 "don't use SSH ControlMaster feature [DEFAULT]"],
1532 DarcsMultipleChoiceOption
1533 [DarcsNoArgOption [] ["http-pipelining"] HTTPPipelining
1534 pipelining_description,
1535 DarcsNoArgOption [] ["no-http-pipelining"] NoHTTPPipelining
1536 no_pipelining_description],
1537 DarcsNoArgOption [] ["no-cache"] NoCache
1538 "don't use patch caches"]
1539 where pipelining_description =
1540 "enable HTTP pipelining"++
1541 (if pipeliningEnabledByDefault then " [DEFAULT]" else "")
1542 no_pipelining_description =
1543 "disable HTTP pipelining"++
1544 (if pipeliningEnabledByDefault then "" else " [DEFAULT]")
1545 \end{code}
1546 \begin{options}
1547 --umask
1548 \end{options}
1549 By default, Darcs will use your current umask. The option
1550 \verb|--umask| will cause Darcs to switch to a different umask before
1551 writing to the repository.
1553 \begin{code}
1554 umask_option :: DarcsOption
1555 umask_option =
1556 DarcsArgOption [] ["umask"] UMask "UMASK"
1557 "specify umask to use when writing"
1558 \end{code}
1560 \begin{options}
1561 --dont-restrict-paths, --restrict-paths
1562 \end{options}
1563 By default darcs is only allowed to manage and modify files and directories
1564 contained inside the current repository and not being part of any darcs
1565 repository's meta data (including the current one). This is mainly for
1566 security, to protect you from spoofed patches modifying arbitrary files
1567 with sensitive data---say, in your home directory---or tempering with any
1568 repository's meta data to switch off this safety guard.
1570 But sometimes you may want to manage a group of ``sub'' repositories'
1571 preference files with a global repository, or use darcs in some other
1572 advanced way. The best way is probably to put
1573 \verb!ALL dont-restrict-paths! in \verb!_darcs/prefs/defaults!. This turns
1574 off all sanity checking for file paths in patches.
1576 Path checking can be temporarily turned on with \verb!--restrict-paths! on
1577 the command line, when pulling or applying unknown patches.
1579 \begin{code}
1580 restrict_paths =
1581 DarcsMultipleChoiceOption
1582 [DarcsNoArgOption [] ["restrict-paths"] RestrictPaths
1583 "don't allow darcs to touch external files or repo metadata",
1584 DarcsNoArgOption [] ["dont-restrict-paths"] DontRestrictPaths
1585 "allow darcs to modify any file or directory (unsafe)"]
1586 \end{code}
1588 \begin{options}
1589 --allow-unrelated-repos
1590 \end{options}
1591 By default darcs checks and warns user if repositories are unrelated when
1592 doing pull, push and send. This option makes darcs skip this check.
1594 \begin{code}
1595 allow_unrelated_repos =
1596 DarcsNoArgOption [] ["ignore-unrelated-repos"] AllowUnrelatedRepos
1597 "do not check if repositories are unrelated"
1598 \end{code}
1600 \begin{code}
1601 -- | @'patch_select_flag' f@ holds whenever @f@ is a way of selecting
1602 -- patches such as @PatchName n@.
1603 patch_select_flag :: DarcsFlag -> Bool
1604 patch_select_flag All = True
1605 patch_select_flag (PatchName _) = True
1606 patch_select_flag (OnePatch _) = True
1607 patch_select_flag (SeveralPatch _) = True
1608 patch_select_flag (AfterPatch _) = True
1609 patch_select_flag (UpToPatch _) = True
1610 patch_select_flag (TagName _) = True
1611 patch_select_flag (LastN _) = True
1612 patch_select_flag (OneTag _) = True
1613 patch_select_flag (AfterTag _) = True
1614 patch_select_flag (UpToTag _) = True
1615 patch_select_flag (OnePattern _) = True
1616 patch_select_flag (SeveralPattern _) = True
1617 patch_select_flag (AfterPattern _) = True
1618 patch_select_flag (UpToPattern _) = True
1619 patch_select_flag _ = False
1620 \end{code}