| 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.
Synopsis
- type DarcsOption = OptSpec DarcsOptDescr Flag
- class YesNo a where
- 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)
- data HooksConfig = HooksConfig {
- pre :: HookConfig
- post :: HookConfig
- data HookConfig = HookConfig {}
- preHook :: DarcsOption a (HookConfig -> a)
- postHook :: DarcsOption a (HookConfig -> a)
- hooks :: DarcsOption a (HooksConfig -> 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
- maxCount :: PrimDarcsOption (Maybe Int)
- data WorkRepo
- workRepo :: PrimDarcsOption WorkRepo
- repoDir :: PrimDarcsOption (Maybe String)
- data RemoteRepos = RemoteRepos [String]
- remoteRepos :: PrimDarcsOption RemoteRepos
- possiblyRemoteRepo :: PrimDarcsOption (Maybe String)
- reponame :: PrimDarcsOption (Maybe String)
- data NotInRemote
- notInRemote :: PrimDarcsOption [NotInRemote]
- notInRemoteFlagName :: String
- data RepoCombinator
- repoCombinator :: PrimDarcsOption RepoCombinator
- allowUnrelatedRepos :: PrimDarcsOption Bool
- justThisRepo :: PrimDarcsOption Bool
- data WithWorkingDir
- withWorkingDir :: 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
- lookforadds :: LookForAdds -> PrimDarcsOption LookForAdds
- lookforreplaces :: PrimDarcsOption LookForReplaces
- lookformoves :: PrimDarcsOption LookForMoves
- data UseIndex
- data ScanKnown
- data IncludeBoring
- includeBoring :: PrimDarcsOption IncludeBoring
- 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
- data ExternalDiff = ExternalDiff {}
- extDiff :: PrimDarcsOption ExternalDiff
- data TestChanges
- testChanges :: PrimDarcsOption TestChanges
- data RunTest
- runTest :: 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
- conflictsNo :: PrimDarcsOption (Maybe AllowConflicts)
- conflictsYes :: PrimDarcsOption (Maybe AllowConflicts)
- data ExternalMerge
- externalMerge :: PrimDarcsOption ExternalMerge
- data Compression
- compress :: PrimDarcsOption Compression
- usePacks :: PrimDarcsOption Bool
- data WithPatchIndex
- patchIndexNo :: 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 Summary
- maybeSummary :: Maybe 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
- machineReadable :: PrimDarcsOption Bool
- data CloneKind
- cloneKind :: 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 EnumPatches
- enumPatches :: PrimDarcsOption EnumPatches
- data GzcrcsAction
- gzcrcsActions :: PrimDarcsOption (Maybe GzcrcsAction)
- siblings :: PrimDarcsOption [AbsolutePath]
- 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.
Minimal complete definition
Instances
| YesNo WithWorkingDir Source # | |
Defined in Darcs.UI.Options.All | |
| YesNo WantGuiPause Source # | |
Defined in Darcs.UI.Options.All | |
| YesNo UseIndex Source # | |
| YesNo LeaveTestDir Source # | |
Defined in Darcs.UI.Options.All | |
| YesNo SetScriptsExecutable Source # | |
Defined in Darcs.UI.Options.All | |
| YesNo RunTest Source # | |
| YesNo IncludeBoring Source # | |
Defined in Darcs.UI.Options.All | |
| YesNo LookForMoves Source # | |
Defined in Darcs.UI.Options.All | |
| YesNo LookForReplaces Source # | |
Defined in Darcs.UI.Options.All | |
| YesNo LookForAdds Source # | |
Defined in Darcs.UI.Options.All | |
| YesNo DryRun Source # | |
| YesNo UseCache Source # | |
| YesNo Reorder Source # | |
| YesNo WithPatchIndex Source # | |
Defined in Darcs.UI.Options.All | |
| YesNo Compression Source # | |
Defined in Darcs.UI.Options.All | |
| YesNo Summary Source # | |
| YesNo WithContext Source # | |
Defined in Darcs.UI.Options.All | |
| YesNo XmlOutput Source # | |
| YesNo EnumPatches Source # | |
Defined in Darcs.UI.Options.All | |
data RootAction Source #
Options for darcs iself that act like sub-commands.
Constructors
| RootHelp | |
| Version | |
| ExactVersion | |
| ListCommands |
Instances
| Eq RootAction Source # | |
Defined in Darcs.UI.Options.All | |
| Show RootAction Source # | |
Defined in Darcs.UI.Options.All Methods showsPrec :: Int -> RootAction -> ShowS # show :: RootAction -> String # showList :: [RootAction] -> ShowS # | |
data StdCmdAction Source #
Constructors
| Help | |
| ListOptions | |
| Disable |
Instances
| Eq StdCmdAction Source # | |
Defined in Darcs.UI.Options.All | |
| Show StdCmdAction Source # | |
Defined in Darcs.UI.Options.All Methods showsPrec :: Int -> StdCmdAction -> ShowS # show :: StdCmdAction -> String # showList :: [StdCmdAction] -> ShowS # | |
anyVerbosity :: DarcsOption a (Bool -> Bool -> Verbosity -> Bool -> a) Source #
data HooksConfig Source #
Constructors
| HooksConfig | |
Fields
| |
data HookConfig Source #
preHook :: DarcsOption a (HookConfig -> a) Source #
postHook :: DarcsOption a (HookConfig -> a) Source #
hooks :: DarcsOption a (HooksConfig -> a) Source #
Constructors
| YesUseCache | |
| NoUseCache |
dryRun :: PrimDarcsOption DryRun Source #
TODO someone wrote here long ago that any time --dry-run is a possibility automated users should be able to examine the results more easily with --xml. See also issue2397. dryRun w/o xml is currently used in add, pull, and repair.
data WantGuiPause Source #
Constructors
| YesWantGuiPause | |
| NoWantGuiPause |
Instances
| Eq WantGuiPause Source # | |
Defined in Darcs.Repository.Flags | |
| Show WantGuiPause Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> WantGuiPause -> ShowS # show :: WantGuiPause -> String # showList :: [WantGuiPause] -> ShowS # | |
| YesNo WantGuiPause Source # | |
Defined in Darcs.UI.Options.All | |
module Darcs.UI.Options.Matching
data SelectDeps Source #
Constructors
| NoDeps | |
| AutoDeps | |
| PromptDeps |
Instances
| Eq SelectDeps Source # | |
Defined in Darcs.UI.Options.All | |
| Show SelectDeps Source # | |
Defined in Darcs.UI.Options.All Methods showsPrec :: Int -> SelectDeps -> ShowS # show :: SelectDeps -> String # showList :: [SelectDeps] -> ShowS # | |
maxCount :: 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 , taking
the possibility of a failed parse into account.Maybe Int
Constructors
| WorkRepoDir String | |
| WorkRepoPossibleURL String | |
| WorkRepoCurrentDir |
data RemoteRepos Source #
Constructors
| RemoteRepos [String] |
Instances
| Eq RemoteRepos Source # | |
Defined in Darcs.Repository.Flags | |
| Show RemoteRepos Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> RemoteRepos -> ShowS # show :: RemoteRepos -> String # showList :: [RemoteRepos] -> ShowS # | |
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.
data NotInRemote Source #
Constructors
| NotInDefaultRepo | |
| NotInRemotePath String |
data RepoCombinator Source #
Constructors
| Intersection | |
| Union | |
| Complement |
Instances
| Eq RepoCombinator Source # | |
Defined in Darcs.UI.Options.All Methods (==) :: RepoCombinator -> RepoCombinator -> Bool # (/=) :: RepoCombinator -> RepoCombinator -> Bool # | |
| Show RepoCombinator Source # | |
Defined in Darcs.UI.Options.All Methods showsPrec :: Int -> RepoCombinator -> ShowS # show :: RepoCombinator -> String # showList :: [RepoCombinator] -> ShowS # | |
data WithWorkingDir Source #
Constructors
| WithWorkingDir | |
| NoWorkingDir |
Instances
| Eq WithWorkingDir Source # | |
Defined in Darcs.Repository.Flags Methods (==) :: WithWorkingDir -> WithWorkingDir -> Bool # (/=) :: WithWorkingDir -> WithWorkingDir -> Bool # | |
| Show WithWorkingDir Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> WithWorkingDir -> ShowS # show :: WithWorkingDir -> String # showList :: [WithWorkingDir] -> ShowS # | |
| YesNo WithWorkingDir Source # | |
Defined in Darcs.UI.Options.All | |
withWorkingDir :: PrimDarcsOption WithWorkingDir Source #
convert, clone, init
data SetDefault Source #
Constructors
| YesSetDefault Bool | |
| NoSetDefault Bool |
Instances
| Eq SetDefault Source # | |
Defined in Darcs.Repository.Flags | |
| Show SetDefault Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> SetDefault -> ShowS # show :: SetDefault -> String # showList :: [SetDefault] -> ShowS # | |
data AskLongComment Source #
Constructors
| NoEditLongComment | |
| YesEditLongComment | |
| PromptLongComment |
Instances
| Eq AskLongComment Source # | |
Defined in Darcs.UI.Options.All Methods (==) :: AskLongComment -> AskLongComment -> Bool # (/=) :: AskLongComment -> AskLongComment -> Bool # | |
| Show AskLongComment Source # | |
Defined in Darcs.UI.Options.All Methods showsPrec :: Int -> AskLongComment -> ShowS # show :: AskLongComment -> String # showList :: [AskLongComment] -> ShowS # | |
Constructors
| Logfile | |
Fields
| |
Constructors
| LookFor | |
Fields
| |
data LookForAdds Source #
Constructors
| YesLookForAdds | |
| NoLookForAdds |
Instances
| Eq LookForAdds Source # | |
Defined in Darcs.Repository.Flags | |
| Show LookForAdds Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> LookForAdds -> ShowS # show :: LookForAdds -> String # showList :: [LookForAdds] -> ShowS # | |
| YesNo LookForAdds Source # | |
Defined in Darcs.UI.Options.All | |
data LookForMoves Source #
Constructors
| YesLookForMoves | |
| NoLookForMoves |
Instances
| Eq LookForMoves Source # | |
Defined in Darcs.Repository.Flags | |
| Show LookForMoves Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> LookForMoves -> ShowS # show :: LookForMoves -> String # showList :: [LookForMoves] -> ShowS # | |
| YesNo LookForMoves Source # | |
Defined in Darcs.UI.Options.All | |
data LookForReplaces Source #
Constructors
| YesLookForReplaces | |
| NoLookForReplaces |
Instances
| Eq LookForReplaces Source # | |
Defined in Darcs.Repository.Flags Methods (==) :: LookForReplaces -> LookForReplaces -> Bool # (/=) :: LookForReplaces -> LookForReplaces -> Bool # | |
| Show LookForReplaces Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> LookForReplaces -> ShowS # show :: LookForReplaces -> String # showList :: [LookForReplaces] -> ShowS # | |
| YesNo LookForReplaces Source # | |
Defined in Darcs.UI.Options.All | |
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 |
data IncludeBoring Source #
Constructors
| YesIncludeBoring | |
| NoIncludeBoring |
Instances
| Eq IncludeBoring Source # | |
Defined in Darcs.Repository.Flags Methods (==) :: IncludeBoring -> IncludeBoring -> Bool # (/=) :: IncludeBoring -> IncludeBoring -> Bool # | |
| Show IncludeBoring Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> IncludeBoring -> ShowS # show :: IncludeBoring -> String # showList :: [IncludeBoring] -> ShowS # | |
| YesNo IncludeBoring Source # | |
Defined in Darcs.UI.Options.All | |
allowProblematicFilenames :: DarcsOption a (Bool -> Bool -> a) Source #
onlyToFiles :: PrimDarcsOption Bool Source #
TODO: see issue2395
data DiffAlgorithm Source #
Constructors
| PatienceDiff | |
| MyersDiff |
Instances
| Eq DiffAlgorithm Source # | |
Defined in Darcs.Util.Diff Methods (==) :: DiffAlgorithm -> DiffAlgorithm -> Bool # (/=) :: DiffAlgorithm -> DiffAlgorithm -> Bool # | |
| Show DiffAlgorithm Source # | |
Defined in Darcs.Util.Diff Methods showsPrec :: Int -> DiffAlgorithm -> ShowS # show :: DiffAlgorithm -> String # showList :: [DiffAlgorithm] -> ShowS # | |
data WithContext Source #
Constructors
| NoContext | |
| YesContext |
Instances
| Eq WithContext Source # | |
Defined in Darcs.UI.Options.All | |
| Show WithContext Source # | |
Defined in Darcs.UI.Options.All Methods showsPrec :: Int -> WithContext -> ShowS # show :: WithContext -> String # showList :: [WithContext] -> ShowS # | |
| YesNo WithContext Source # | |
Defined in Darcs.UI.Options.All | |
data ExternalDiff Source #
Constructors
| ExternalDiff | |
Instances
| Eq ExternalDiff Source # | |
Defined in Darcs.UI.Options.All | |
| Show ExternalDiff Source # | |
Defined in Darcs.UI.Options.All Methods showsPrec :: Int -> ExternalDiff -> ShowS # show :: ExternalDiff -> String # showList :: [ExternalDiff] -> ShowS # | |
data TestChanges Source #
Constructors
| NoTestChanges | |
| YesTestChanges LeaveTestDir |
Instances
| Eq TestChanges Source # | |
Defined in Darcs.UI.Options.All | |
Constructors
| YesRunTest | |
| NoRunTest |
data LeaveTestDir Source #
Constructors
| YesLeaveTestDir | |
| NoLeaveTestDir |
Instances
| Eq LeaveTestDir Source # | |
Defined in Darcs.Repository.Flags | |
| Show LeaveTestDir Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> LeaveTestDir -> ShowS # show :: LeaveTestDir -> String # showList :: [LeaveTestDir] -> ShowS # | |
| YesNo LeaveTestDir Source # | |
Defined in Darcs.UI.Options.All | |
data HeaderFields Source #
Constructors
| HeaderFields | |
Constructors
| NoVerify | |
| VerifyKeyring AbsolutePath | |
| VerifySSL AbsolutePath |
data AllowConflicts Source #
Instances
| Eq AllowConflicts Source # | |
Defined in Darcs.Repository.Flags Methods (==) :: AllowConflicts -> AllowConflicts -> Bool # (/=) :: AllowConflicts -> AllowConflicts -> Bool # | |
| Show AllowConflicts Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> AllowConflicts -> ShowS # show :: AllowConflicts -> String # showList :: [AllowConflicts] -> ShowS # | |
conflictsNo :: PrimDarcsOption (Maybe AllowConflicts) Source #
push, apply, rebase apply: default to NoAllowConflicts
conflictsYes :: PrimDarcsOption (Maybe AllowConflicts) Source #
pull, rebase pull: default to YesAllowConflictsAndMark
data ExternalMerge Source #
Constructors
| YesExternalMerge String | |
| NoExternalMerge |
Instances
| Eq ExternalMerge Source # | |
Defined in Darcs.Repository.Flags Methods (==) :: ExternalMerge -> ExternalMerge -> Bool # (/=) :: ExternalMerge -> ExternalMerge -> Bool # | |
| Show ExternalMerge Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> ExternalMerge -> ShowS # show :: ExternalMerge -> String # showList :: [ExternalMerge] -> ShowS # | |
data Compression Source #
Constructors
| NoCompression | |
| GzipCompression |
Instances
| Eq Compression Source # | |
Defined in Darcs.Repository.Flags | |
| Show Compression Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> Compression -> ShowS # show :: Compression -> String # showList :: [Compression] -> ShowS # | |
| YesNo Compression Source # | |
Defined in Darcs.UI.Options.All | |
data WithPatchIndex Source #
Constructors
| YesPatchIndex | |
| NoPatchIndex |
Instances
| Eq WithPatchIndex Source # | |
Defined in Darcs.Repository.Flags Methods (==) :: WithPatchIndex -> WithPatchIndex -> Bool # (/=) :: WithPatchIndex -> WithPatchIndex -> Bool # | |
| Show WithPatchIndex Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> WithPatchIndex -> ShowS # show :: WithPatchIndex -> String # showList :: [WithPatchIndex] -> ShowS # | |
| YesNo WithPatchIndex Source # | |
Defined in Darcs.UI.Options.All | |
Constructors
| Output AbsolutePathOrStd | |
| OutputAutoName AbsolutePath |
Constructors
| NoSummary | |
| YesSummary |
maybeSummary :: Maybe Summary -> PrimDarcsOption (Maybe Summary) Source #
data RemoteDarcs Source #
Constructors
| RemoteDarcs String | |
| DefaultRemoteDarcs |
Instances
| Eq RemoteDarcs Source # | |
Defined in Darcs.Repository.Flags | |
| Show RemoteDarcs Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> RemoteDarcs -> ShowS # show :: RemoteDarcs -> String # showList :: [RemoteDarcs] -> ShowS # | |
data NetworkOptions Source #
TODO: reconsider this grouping of options
Constructors
| NetworkOptions | |
Fields | |
data SetScriptsExecutable Source #
Constructors
| YesSetScriptsExecutable | |
| NoSetScriptsExecutable |
Instances
| Eq SetScriptsExecutable Source # | |
Defined in Darcs.Repository.Flags Methods (==) :: SetScriptsExecutable -> SetScriptsExecutable -> Bool # (/=) :: SetScriptsExecutable -> SetScriptsExecutable -> Bool # | |
| Show SetScriptsExecutable Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> SetScriptsExecutable -> ShowS # show :: SetScriptsExecutable -> String # showList :: [SetScriptsExecutable] -> ShowS # | |
| YesNo SetScriptsExecutable Source # | |
Defined in Darcs.UI.Options.All | |
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 |
data PatchFormat Source #
Constructors
| PatchFormat1 | |
| PatchFormat2 |
Instances
| Eq PatchFormat Source # | |
Defined in Darcs.Repository.Flags | |
| Show PatchFormat Source # | |
Defined in Darcs.Repository.Flags Methods showsPrec :: Int -> PatchFormat -> ShowS # show :: PatchFormat -> String # showList :: [PatchFormat] -> ShowS # | |
hashed :: PrimDarcsOption () Source #
Deprecated flag, still present to output an error message.
data ChangesFormat Source #
Instances
| Eq ChangesFormat Source # | |
Defined in Darcs.UI.Options.All Methods (==) :: ChangesFormat -> ChangesFormat -> Bool # (/=) :: ChangesFormat -> ChangesFormat -> Bool # | |
| Show ChangesFormat Source # | |
Defined in Darcs.UI.Options.All Methods showsPrec :: Int -> ChangesFormat -> ShowS # show :: ChangesFormat -> String # showList :: [ChangesFormat] -> ShowS # | |
data TestStrategy Source #
Instances
| Eq TestStrategy Source # | |
Defined in Darcs.UI.Options.All | |
| Show TestStrategy Source # | |
Defined in Darcs.UI.Options.All Methods showsPrec :: Int -> TestStrategy -> ShowS # show :: TestStrategy -> String # showList :: [TestStrategy] -> ShowS # | |
data EnumPatches Source #
Constructors
| NoEnumPatches | |
| YesEnumPatches |
Instances
| Eq EnumPatches Source # | |
Defined in Darcs.UI.Options.All | |
| Show EnumPatches Source # | |
Defined in Darcs.UI.Options.All Methods showsPrec :: Int -> EnumPatches -> ShowS # show :: EnumPatches -> String # showList :: [EnumPatches] -> ShowS # | |
| YesNo EnumPatches Source # | |
Defined in Darcs.UI.Options.All | |
data GzcrcsAction Source #
Constructors
| GzcrcsCheck | |
| GzcrcsRepair |
Instances
| Eq GzcrcsAction Source # | |
Defined in Darcs.UI.Options.All | |
| Show GzcrcsAction Source # | |
Defined in Darcs.UI.Options.All Methods showsPrec :: Int -> GzcrcsAction -> ShowS # show :: GzcrcsAction -> String # showList :: [GzcrcsAction] -> ShowS # | |