| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Darcs.UI.Options.All
Description
All the concrete options.
Notes:
- The term "option" refers to a flag or combination of flags that together form a part of a command's configuration. Ideally, options should be orthogonal to each other, so we can freely combine them.
- A primitive (indivisible) option has an associate value type.
- An option named "xyzActions" represents a set of flags that act as mutually exclusive sub-commands. They typically have a dedicated value type named "XyzAction".
- This module is probably best imported qualified. This is in contrast to
    the current practice of using subtly differing names to avoid name
    clashes for closely related items. For instance, the data constructors
    for an option's value type and the corresponding data constructors in
    DarcsFlagmay coincide. This is also why we import Darcs.UI.Flags qualified here.
- When the new options system is finally in place, no code other than the
    one for constructing options should directly refer to DarcsFlagconstructors.
- type DarcsOption = OptSpec DarcsOptDescr Flag
- data RootAction
- rootActions :: PrimDarcsOption (Maybe RootAction)
- data StdCmdAction- = Help
- | ListOptions
- | Disable
 
- stdCmdActions :: PrimDarcsOption (Maybe StdCmdAction)
- debug :: PrimDarcsOption Bool
- data Verbosity
- verbosity :: PrimDarcsOption Verbosity
- timings :: PrimDarcsOption Bool
- anyVerbosity :: DarcsOption a (Bool -> Bool -> Verbosity -> Bool -> a)
- preHook :: DarcsOption a (Maybe String -> Bool -> a)
- postHook :: DarcsOption a (Maybe String -> Bool -> a)
- hooks :: DarcsOption a (Maybe String -> Bool -> Maybe String -> Bool -> a)
- data UseCache
- useCache :: PrimDarcsOption UseCache
- data XmlOutput
- xmloutput :: PrimDarcsOption XmlOutput
- data DryRun
- dryRun :: PrimDarcsOption DryRun
- dryRunXml :: DarcsOption a (DryRun -> XmlOutput -> a)
- interactive :: PrimDarcsOption (Maybe Bool)
- pipe :: PrimDarcsOption Bool
- data WantGuiPause
- pauseForGui :: PrimDarcsOption WantGuiPause
- askdeps :: PrimDarcsOption Bool
- module Darcs.UI.Options.Matching
- data SelectDeps- = NoDeps
- | AutoDeps
- | PromptDeps
 
- selectDeps :: PrimDarcsOption SelectDeps
- changesReverse :: PrimDarcsOption Bool
- matchMaxcount :: PrimDarcsOption (Maybe Int)
- data WorkRepo
- workRepo :: PrimDarcsOption WorkRepo
- workingRepoDir :: PrimDarcsOption (Maybe String)
- data RemoteRepos = RemoteRepos [String]
- remoteRepos :: PrimDarcsOption RemoteRepos
- possiblyRemoteRepo :: PrimDarcsOption (Maybe String)
- reponame :: PrimDarcsOption (Maybe String)
- notInRemote :: PrimDarcsOption [Maybe String]
- notInRemoteFlagName :: String
- data RepoCombinator
- repoCombinator :: PrimDarcsOption RepoCombinator
- allowUnrelatedRepos :: PrimDarcsOption Bool
- justThisRepo :: PrimDarcsOption Bool
- data WithWorkingDir
- useWorkingDir :: PrimDarcsOption WithWorkingDir
- data SetDefault
- setDefault :: PrimDarcsOption (Maybe Bool)
- patchname :: PrimDarcsOption (Maybe String)
- author :: PrimDarcsOption (Maybe String)
- data AskLongComment
- askLongComment :: PrimDarcsOption (Maybe AskLongComment)
- keepDate :: PrimDarcsOption Bool
- data Logfile = Logfile {}
- logfile :: PrimDarcsOption Logfile
- data LookFor = LookFor {}
- data LookForAdds
- data LookForMoves
- data LookForReplaces
- lookfor :: PrimDarcsOption LookFor
- data UseIndex
- data ScanKnown
- diffing :: PrimDarcsOption (UseIndex, ScanKnown, DiffAlgorithm)
- includeBoring :: PrimDarcsOption Bool
- allowProblematicFilenames :: DarcsOption a (Bool -> Bool -> a)
- allowCaseDifferingFilenames :: PrimDarcsOption Bool
- allowWindowsReservedFilenames :: PrimDarcsOption Bool
- onlyToFiles :: PrimDarcsOption Bool
- useIndex :: PrimDarcsOption UseIndex
- recursive :: PrimDarcsOption Bool
- data DiffAlgorithm
- diffAlgorithm :: PrimDarcsOption DiffAlgorithm
- data WithContext
- withContext :: PrimDarcsOption WithContext
- unidiff :: PrimDarcsOption Bool
- data ExternalDiff = ExternalDiff {}
- extDiff :: PrimDarcsOption ExternalDiff
- data TestChanges
- testChanges :: PrimDarcsOption TestChanges
- data RunTest
- test :: PrimDarcsOption RunTest
- data LeaveTestDir
- leaveTestDir :: PrimDarcsOption LeaveTestDir
- data HeaderFields = HeaderFields {}
- headerFields :: PrimDarcsOption HeaderFields
- sendToContext :: PrimDarcsOption (Maybe AbsolutePath)
- sendmail :: PrimDarcsOption (Bool, Maybe String)
- sendmailCmd :: PrimDarcsOption (Maybe String)
- charset :: PrimDarcsOption (Maybe String)
- editDescription :: PrimDarcsOption Bool
- ccApply :: PrimDarcsOption (Maybe String)
- reply :: PrimDarcsOption (Maybe String)
- happyForwarding :: PrimDarcsOption Bool
- applyAs :: PrimDarcsOption (Maybe String)
- data Sign
- sign :: PrimDarcsOption Sign
- data Verify
- verify :: PrimDarcsOption Verify
- data AllowConflicts
- conflicts :: AllowConflicts -> PrimDarcsOption (Maybe AllowConflicts)
- data ExternalMerge
- useExternalMerge :: PrimDarcsOption ExternalMerge
- data Compression
- compress :: PrimDarcsOption Compression
- usePacks :: PrimDarcsOption Bool
- data WithPatchIndex
- patchIndex :: PrimDarcsOption WithPatchIndex
- patchIndexYes :: PrimDarcsOption WithPatchIndex
- data Reorder
- reorder :: PrimDarcsOption Reorder
- minimize :: PrimDarcsOption Bool
- storeInMemory :: PrimDarcsOption Bool
- data Output
- output :: PrimDarcsOption (Maybe Output)
- data Summary
- summary :: PrimDarcsOption (Maybe Summary)
- data RemoteDarcs
- data NetworkOptions = NetworkOptions {}
- network :: PrimDarcsOption NetworkOptions
- data UMask
- umask :: PrimDarcsOption UMask
- data SetScriptsExecutable
- setScriptsExecutable :: PrimDarcsOption SetScriptsExecutable
- restrictPaths :: PrimDarcsOption Bool
- amendUnrecord :: PrimDarcsOption Bool
- selectAuthor :: PrimDarcsOption Bool
- humanReadable :: PrimDarcsOption Bool
- machineReadable :: PrimDarcsOption Bool
- data CloneKind
- partial :: PrimDarcsOption CloneKind
- distname :: PrimDarcsOption (Maybe String)
- distzip :: PrimDarcsOption Bool
- marks :: DarcsOption a (Maybe String -> Maybe String -> a)
- readMarks :: PrimDarcsOption (Maybe String)
- writeMarks :: PrimDarcsOption (Maybe String)
- data PatchFormat
- patchFormat :: PrimDarcsOption PatchFormat
- hashed :: PrimDarcsOption ()
- data ChangesFormat
- changesFormat :: PrimDarcsOption (Maybe ChangesFormat)
- tokens :: PrimDarcsOption (Maybe String)
- forceReplace :: PrimDarcsOption Bool
- data TestStrategy
- testStrategy :: PrimDarcsOption TestStrategy
- files :: PrimDarcsOption Bool
- directories :: PrimDarcsOption Bool
- pending :: PrimDarcsOption Bool
- nullFlag :: PrimDarcsOption Bool
- data GzcrcsAction
- gzcrcsActions :: PrimDarcsOption (Maybe GzcrcsAction)
- siblings :: PrimDarcsOption [AbsolutePath]
- reorderPatches :: PrimDarcsOption Bool
- optimizePatchIndex :: PrimDarcsOption (Maybe WithPatchIndex)
Documentation
type DarcsOption = OptSpec DarcsOptDescr Flag Source
DarcsOption instantiates the first two type parameters of OptSpec to
 what we need in darcs. The first parameter is instantiated to
 The flag type is instantiate to Flag.
data RootAction Source
Options for darcs iself that act like sub-commands.
Constructors
| RootHelp | |
| Version | |
| ExactVersion | |
| ListCommands | 
Instances
Constructors
| Quiet | |
| NormalVerbosity | |
| Verbose | 
anyVerbosity :: DarcsOption a (Bool -> Bool -> Verbosity -> Bool -> a) Source
Constructors
| YesUseCache | |
| NoUseCache | 
dryRun :: PrimDarcsOption DryRun Source
NOTE: I'd rather work to have no uses of dryRunNoxml, so that any time --dry-run is a possibility, automated users can examine the results more easily with --xml.
See also issue2397.
dryRunXml :: DarcsOption a (DryRun -> XmlOutput -> a) Source
module Darcs.UI.Options.Matching
matchMaxcount :: PrimDarcsOption (Maybe Int) Source
TODO: Returning -1 if the argument cannot be parsed as an integer is
 not something I expected to find in a Haskell program. Instead, the flag
 should take either a plain String argument (leaving it to a later stage
 to parse the String to an Int), or else a Maybe Int
Constructors
| WorkRepoDir String | |
| WorkRepoPossibleURL String | |
| WorkRepoCurrentDir | 
reponame :: PrimDarcsOption (Maybe String) Source
--repodir is there for compatibility, should be removed eventually
IMHO the whole option can disappear; it overlaps with using an extra (non-option)
 argument, which is how e.g. darcs get is usually invoked.
useWorkingDir :: PrimDarcsOption WithWorkingDir Source
convert, clone, init
data AskLongComment Source
Constructors
| NoEditLongComment | |
| YesEditLongComment | |
| PromptLongComment | 
Instances
Constructors
| Logfile | |
| Fields 
 | |
Constructors
| LookFor | |
| Fields 
 | |
Constructors
| UseIndex | |
| IgnoreIndex | 
Constructors
| ScanKnown | Just files already known to darcs | 
| ScanAll | All files, i.e. look for new ones | 
| ScanBoring | All files, even boring ones | 
allowProblematicFilenames :: DarcsOption a (Bool -> Bool -> a) Source
onlyToFiles :: PrimDarcsOption Bool Source
TODO: see issue2395
data ExternalDiff Source
Instances
data HeaderFields Source
Constructors
| HeaderFields | |
Constructors
| NoVerify | |
| VerifyKeyring AbsolutePath | |
| VerifySSL AbsolutePath | 
data AllowConflicts Source
Instances
Constructors
| Output AbsolutePathOrStd | |
| OutputAutoName AbsolutePath | 
data NetworkOptions Source
TODO: reconsider this grouping of options
Constructors
| NetworkOptions | |
| Fields | |
data SetScriptsExecutable Source
Constructors
| YesSetScriptsExecutable | |
| NoSetScriptsExecutable | 
humanReadable :: PrimDarcsOption Bool Source
TODO: These should be mutually exclusive, but are they? The code is almost inscrutable.
machineReadable :: PrimDarcsOption Bool Source
See above.
Constructors
| LazyClone | Just copy pristine and inventories | 
| NormalClone | First do a lazy clone then copy everything | 
| CompleteClone | Same as Normal but omit telling user they can interrumpt | 
hashed :: PrimDarcsOption () Source
Deprecated flag, still present to output an error message.
data ChangesFormat Source
Constructors
| HumanReadable | |
| GenContext | |
| GenXml | |
| NumberPatches | |
| CountPatches | 
Instances
data TestStrategy Source
Instances