- data DarcsFlag
- = Help
- | ListOptions
- | NoTest
- | Test
- | OnlyChangesToFiles
- | ChangesToAllFiles
- | LeaveTestDir
- | NoLeaveTestDir
- | Timings
- | Debug
- | DebugVerbose
- | DebugHTTP
- | Verbose
- | NormalVerbosity
- | Quiet
- | Target String
- | Cc String
- | Output AbsolutePathOrStd
- | OutputAutoName AbsolutePath
- | Subject String
- | InReplyTo String
- | SendmailCmd String
- | Author String
- | PatchName String
- | OnePatch String
- | SeveralPatch String
- | AfterPatch String
- | UpToPatch String
- | TagName String
- | LastN Int
- | MaxCount Int
- | PatchIndexRange Int Int
- | NumberPatches
- | OneTag String
- | AfterTag String
- | UpToTag String
- | Context AbsolutePath
- | Count
- | LogFile AbsolutePath
- | RmLogFile
- | DontRmLogFile
- | DistName String
- | All
- | Recursive
- | NoRecursive
- | Reorder
- | RestrictPaths
- | DontRestrictPaths
- | AskDeps
- | NoAskDeps
- | IgnoreTimes
- | DontIgnoreTimes
- | LookForAdds
- | NoLookForAdds
- | AnyOrder
- | CreatorHash String
- | Intersection
- | Union
- | Complement
- | Sign
- | SignAs String
- | NoSign
- | SignSSL String
- | HappyForwarding
- | NoHappyForwarding
- | Verify AbsolutePath
- | VerifySSL AbsolutePath
- | SSHControlMaster
- | NoSSHControlMaster
- | RemoteDarcs String
- | EditDescription
- | NoEditDescription
- | Toks String
- | EditLongComment
- | NoEditLongComment
- | PromptLongComment
- | AllowConflicts
- | MarkConflicts
- | NoAllowConflicts
- | SkipConflicts
- | Boring
- | SkipBoring
- | AllowCaseOnly
- | DontAllowCaseOnly
- | AllowWindowsReserved
- | DontAllowWindowsReserved
- | DontGrabDeps
- | DontPromptForDependencies
- | PromptForDependencies
- | Compress
- | NoCompress
- | UnCompress
- | WorkRepoDir String
- | WorkRepoUrl String
- | RemoteRepo String
- | NewRepo String
- | Reply String
- | ApplyAs String
- | MachineReadable
- | HumanReadable
- | Pipe
- | Interactive
- | DiffCmd String
- | ExternalMerge String
- | Summary
- | NoSummary
- | Unified
- | NonUnified
- | Reverse
- | Forward
- | Partial
- | Complete
- | Lazy
- | Ephemeral
- | FixFilePath AbsolutePath AbsolutePath
- | DiffFlags String
- | XMLOutput
- | ForceReplace
- | OnePattern PatchMatch
- | SeveralPattern PatchMatch
- | AfterPattern PatchMatch
- | UpToPattern PatchMatch
- | NonApply
- | NonVerify
- | NonForce
- | DryRun
- | SetDefault
- | NoSetDefault
- | FancyMoveAdd
- | NoFancyMoveAdd
- | Disable
- | SetScriptsExecutable
- | DontSetScriptsExecutable
- | UseHashedInventory
- | UseOldFashionedInventory
- | UseFormat2
- | PristinePlain
- | PristineNone
- | NoUpdateWorking
- | Sibling AbsolutePath
- | Relink
- | RelinkPristine
- | NoLinks
- | OptimizePristine
- | UpgradeFormat
- | Files
- | NoFiles
- | Directories
- | NoDirectories
- | Pending
- | NoPending
- | PosthookCmd String
- | NoPosthook
- | AskPosthook
- | RunPosthook
- | PrehookCmd String
- | NoPrehook
- | AskPrehook
- | RunPrehook
- | UMask String
- | StoreInMemory
- | ApplyOnDisk
- | HTTPPipelining
- | NoHTTPPipelining
- | NoCache
- | AllowUnrelatedRepos
- | Check
- | Repair
- | JustThisRepo
- | NullFlag
- flagToString :: [DarcsOption] -> DarcsFlag -> Maybe String
- maxCount :: [DarcsFlag] -> Maybe Int
- isin :: (String -> DarcsFlag) -> [DarcsFlag] -> Bool
- arein :: [DarcsOption] -> [DarcsFlag] -> Bool
- definePatches :: RepoPatch p => FL (PatchInfoAnd p) -> IO ()
- defineChanges :: Patchy p => p -> IO ()
- fixFilePathOrStd :: [DarcsFlag] -> FilePath -> IO AbsolutePathOrStd
- fixUrl :: [DarcsFlag] -> String -> IO String
- fixSubPaths :: [DarcsFlag] -> [FilePath] -> IO [SubPath]
- areFileArgs :: [SubPath] -> Bool
- data DarcsOption
- = DarcsArgOption [Char] [String] (String -> DarcsFlag) String String
- | DarcsAbsPathOption [Char] [String] (AbsolutePath -> DarcsFlag) String String
- | DarcsAbsPathOrStdOption [Char] [String] (AbsolutePathOrStd -> DarcsFlag) String String
- | DarcsOptAbsPathOption [Char] [String] String (AbsolutePath -> DarcsFlag) String String
- | DarcsNoArgOption [Char] [String] DarcsFlag String
- | DarcsMultipleChoiceOption [DarcsOption]
- optionFromDarcsoption :: AbsolutePath -> DarcsOption -> [OptDescr DarcsFlag]
- help :: DarcsOption
- listOptions :: DarcsOption
- listFiles :: IO [String]
- anyVerbosity :: [DarcsOption]
- disable :: DarcsOption
- restrictPaths :: DarcsOption
- notest :: DarcsOption
- test :: DarcsOption
- workingRepoDir :: DarcsOption
- testByDefault :: [DarcsFlag] -> [DarcsFlag]
- remoteRepo :: DarcsOption
- leaveTestDir :: DarcsOption
- possiblyRemoteRepoDir :: DarcsOption
- getRepourl :: [DarcsFlag] -> Maybe String
- listRegisteredFiles :: IO [String]
- listUnregisteredFiles :: IO [String]
- author :: DarcsOption
- getAuthor :: [DarcsFlag] -> IO String
- getEasyAuthor :: IO (Maybe String)
- getSendmailCmd :: [DarcsFlag] -> IO String
- fileHelpAuthor :: [String]
- environmentHelpEmail :: ([String], [String])
- patchnameOption :: DarcsOption
- distnameOption :: DarcsOption
- logfile :: DarcsOption
- rmlogfile :: DarcsOption
- fromOpt :: DarcsOption
- subject :: DarcsOption
- getSubject :: [DarcsFlag] -> Maybe String
- inReplyTo :: DarcsOption
- getInReplyTo :: [DarcsFlag] -> Maybe String
- target :: DarcsOption
- ccSend :: DarcsOption
- ccApply :: DarcsOption
- getCc :: [DarcsFlag] -> String
- output :: DarcsOption
- outputAutoName :: DarcsOption
- recursive :: String -> DarcsOption
- inventoryChoices :: DarcsOption
- getInventoryChoices :: DarcsOption
- upgradeFormat :: DarcsOption
- askdeps :: DarcsOption
- ignoretimes :: DarcsOption
- lookforadds :: DarcsOption
- askLongComment :: DarcsOption
- sendmailCmd :: DarcsOption
- environmentHelpSendmail :: ([String], [String])
- sign :: DarcsOption
- verify :: DarcsOption
- editDescription :: DarcsOption
- reponame :: DarcsOption
- creatorhash :: DarcsOption
- applyConflictOptions :: DarcsOption
- reply :: DarcsOption
- pullConflictOptions :: DarcsOption
- useExternalMerge :: DarcsOption
- depsSel :: DarcsOption
- nocompress :: DarcsOption
- uncompressNocompress :: DarcsOption
- repoCombinator :: DarcsOption
- optionsLatex :: [DarcsOption] -> String
- reorderPatches :: DarcsOption
- noskipBoring :: DarcsOption
- allowProblematicFilenames :: DarcsOption
- applyas :: DarcsOption
- humanReadable :: DarcsOption
- changesReverse :: DarcsOption
- onlyToFiles :: DarcsOption
- changesFormat :: DarcsOption
- matchOneContext :: DarcsOption
- matchOneNontag :: DarcsOption
- matchMaxcount :: DarcsOption
- sendToContext :: DarcsOption
- getContext :: [DarcsFlag] -> Maybe AbsolutePath
- pipeInteractive :: DarcsOption
- allInteractive :: DarcsOption
- allPipeInteractive :: DarcsOption
- summary :: DarcsOption
- unified :: DarcsOption
- tokens :: DarcsOption
- partial :: DarcsOption
- partialCheck :: DarcsOption
- diffCmdFlag :: DarcsOption
- diffflags :: DarcsOption
- unidiff :: DarcsOption
- xmloutput :: DarcsOption
- forceReplace :: DarcsOption
- dryRun :: [DarcsOption]
- dryRunNoxml :: DarcsOption
- printDryRunMessageAndExit :: RepoPatch p => String -> [DarcsFlag] -> FL (PatchInfoAnd p) -> IO ()
- showFriendly :: Patchy p => [DarcsFlag] -> p -> Doc
- matchOne :: DarcsOption
- matchSeveral :: DarcsOption
- matchRange :: DarcsOption
- matchSeveralOrRange :: DarcsOption
- happyForwarding :: DarcsOption
- matchSeveralOrLast :: DarcsOption
- setDefault :: DarcsOption
- fancyMoveAdd :: DarcsOption
- setScriptsExecutableOption :: DarcsOption
- sibling :: DarcsOption
- flagsToSiblings :: [DarcsFlag] -> [AbsolutePath]
- relink :: DarcsOption
- relinkPristine :: DarcsOption
- nolinks :: DarcsOption
- files :: DarcsOption
- directories :: DarcsOption
- pending :: DarcsOption
- posthookCmd :: DarcsOption
- posthookPrompt :: DarcsOption
- getPosthookCmd :: [DarcsFlag] -> Maybe String
- prehookCmd :: DarcsOption
- prehookPrompt :: DarcsOption
- getPrehookCmd :: [DarcsFlag] -> Maybe String
- nullFlag :: DarcsOption
- umaskOption :: DarcsOption
- storeInMemory :: DarcsOption
- patchSelectFlag :: DarcsFlag -> Bool
- networkOptions :: [DarcsOption]
- noCache :: DarcsOption
- allowUnrelatedRepos :: DarcsOption
- checkOrRepair :: DarcsOption
- justThisRepo :: DarcsOption
- optimizePristine :: DarcsOption
Documentation
The DarcsFlag
type is a list of all flags that can ever be
passed to darcs, or to one of its commands.
flagToString :: [DarcsOption] -> DarcsFlag -> Maybe StringSource
arein :: [DarcsOption] -> [DarcsFlag] -> BoolSource
definePatches :: RepoPatch p => FL (PatchInfoAnd p) -> IO ()Source
defineChanges :: Patchy p => p -> IO ()Source
fixFilePathOrStd :: [DarcsFlag] -> FilePath -> IO AbsolutePathOrStdSource
areFileArgs :: [SubPath] -> BoolSource
data DarcsOption Source
A type for darcs' options. The value contains the command line
switch(es) for the option, a help string, and a function to build a
DarcsFlag
from the command line arguments. for each constructor,
shortSwitches
represents the list of short command line switches
which invoke the option, longSwitches the list of long command line
switches, optDescr the description of the option, and argDescr the description
of its argument, if any. mkFlag is a function which makes a DarcsFlag
from
the arguments of the option.
DarcsArgOption [Char] [String] (String -> DarcsFlag) String String |
|
DarcsAbsPathOption [Char] [String] (AbsolutePath -> DarcsFlag) String String |
|
DarcsAbsPathOrStdOption [Char] [String] (AbsolutePathOrStd -> DarcsFlag) String String |
|
DarcsOptAbsPathOption [Char] [String] String (AbsolutePath -> DarcsFlag) String String |
|
DarcsNoArgOption [Char] [String] DarcsFlag String |
|
DarcsMultipleChoiceOption [DarcsOption] | A constructor for grouping related options together, such as
|
listOptions :: DarcsOptionSource
list_option
is an option which lists the command's arguments
listFiles :: IO [String]Source
Get a list of all non-boring files and directories in the working copy.
testByDefault :: [DarcsFlag] -> [DarcsFlag]Source
remoteRepo :: DarcsOptionSource
remoteRepo
is the option used to specify the URL of the remote
repository to work with
getRepourl :: [DarcsFlag] -> Maybe StringSource
getRepourl
takes a list of flags and returns the url of the
repository specified by Repodir "directory"
in that list of flags, if any.
This flag is present if darcs was invoked with --repodir=DIRECTORY
listRegisteredFiles :: IO [String]Source
listRegisteredFiles
returns the list of all registered files in the repository.
listUnregisteredFiles :: IO [String]Source
listUnregisteredFiles
returns the list of all non-boring unregistered
files in the repository.
getAuthor :: [DarcsFlag] -> IO StringSource
getAuthor
takes a list of flags and returns the author of the
change specified by Author "Leo Tolstoy"
in that list of flags, if any.
Otherwise, if Pipe
is present, asks the user who is the author and
returns the answer. If neither are present, try to guess the author,
from _darcs/prefs
, and if it's not possible, ask the user.
getEasyAuthor :: IO (Maybe String)Source
getEasyAuthor
tries to get the author name first from the repository preferences,
then from global preferences, then from environment variables. Returns Nothing
if it
could not get it.
getSendmailCmd :: [DarcsFlag] -> IO StringSource
getSendmailCmd
takes a list of flags and returns the sendmail command
to be used by darcs send
. Looks for a command specified by
SendmailCmd "command"
in that list of flags, if any.
This flag is present if darcs was invoked with --sendmail-command=COMMAND
Alternatively the user can set $S
ENDMAIL
which will be used as a fallback if present.
environmentHelpEmail :: ([String], [String])Source
getSubject :: [DarcsFlag] -> Maybe StringSource
getSubject
takes a list of flags and returns the subject of the mail
to be sent by darcs send
. Looks for a subject specified by
Subject "subject"
in that list of flags, if any.
This flag is present if darcs was invoked with --subject=SUBJECT
getInReplyTo :: [DarcsFlag] -> Maybe StringSource
getCc :: [DarcsFlag] -> StringSource
getCc
takes a list of flags and returns the addresses to send a copy of
the patch bundle to when using darcs send
.
looks for a cc address specified by Cc "address"
in that list of flags.
Returns the addresses as a comma separated string.
recursive :: String -> DarcsOptionSource
environmentHelpSendmail :: ([String], [String])Source
optionsLatex :: [DarcsOption] -> StringSource
getContext :: [DarcsFlag] -> Maybe AbsolutePathSource
getContext
takes a list of flags and returns the context
specified by Context c
in that list of flags, if any.
This flag is present if darcs was invoked with --context=FILE
dryRun :: [DarcsOption]Source
printDryRunMessageAndExit :: RepoPatch p => String -> [DarcsFlag] -> FL (PatchInfoAnd p) -> IO ()Source
prints a string
representing the action that would be taken if the printDryRunMessageAndExit
action opts patches--dry-run
option
had not been passed to darcs. Then darcs exits successfully.
action
is the name of the action being taken, like "push"
opts
is the list of flags which were sent to darcs
patches
is the sequence of patches which would be touched by action
.
showFriendly :: Patchy p => [DarcsFlag] -> p -> DocSource
returns a showFriendly
flags patchDoc
representing the right
way to show patch
given the list flags
of flags darcs was invoked with.
flagsToSiblings :: [DarcsFlag] -> [AbsolutePath]Source
flagsToSiblings
collects the contents of all Sibling
flags in a list of flags.
getPosthookCmd :: [DarcsFlag] -> Maybe StringSource
getPosthookCmd
takes a list of flags and returns the posthook command
specified by PosthookCmd a
in that list of flags, if any.
getPrehookCmd :: [DarcsFlag] -> Maybe StringSource
getPrehookCmd
takes a list of flags and returns the prehook command
specified by PrehookCmd a
in that list of flags, if any.
patchSelectFlag :: DarcsFlag -> BoolSource
holds whenever patchSelectFlag
ff
is a way of selecting
patches such as PatchName n
.