Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
DarcsFlag
may 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
DarcsFlag
constructors.
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
- debugging :: DarcsOption a (Bool -> 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)
- repoDir :: PrimDarcsOption (Maybe String)
- possiblyRemoteRepo :: PrimDarcsOption (Maybe String)
- newRepo :: 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)
- data InheritDefault
- inheritDefault :: PrimDarcsOption InheritDefault
- data WithPrefsTemplates
- withPrefsTemplates :: PrimDarcsOption WithPrefsTemplates
- patchname :: PrimDarcsOption (Maybe String)
- author :: PrimDarcsOption (Maybe String)
- data AskLongComment
- askLongComment :: PrimDarcsOption (Maybe AskLongComment)
- keepDate :: PrimDarcsOption Bool
- data Logfile = Logfile {}
- logfile :: PrimDarcsOption Logfile
- data UseIndex
- includeBoring :: PrimDarcsOption Bool
- data LookForAdds
- data LookForMoves
- data LookForReplaces
- data DiffOpts = DiffOpts {}
- lookforadds :: PrimDarcsOption LookForAdds
- maybelookforadds :: LookForAdds -> PrimDarcsOption LookForAdds
- lookforreplaces :: PrimDarcsOption LookForReplaces
- lookformoves :: PrimDarcsOption LookForMoves
- 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 {
- diffCmd :: Maybe String
- diffOptions :: [String]
- diffUnified :: Bool
- extDiff :: PrimDarcsOption ExternalDiff
- data TestChanges
- testChanges :: PrimDarcsOption TestChanges
- data RunTest
- data LeaveTestDir
- leaveTestDir :: PrimDarcsOption LeaveTestDir
- data HeaderFields = HeaderFields {}
- headerFields :: PrimDarcsOption HeaderFields
- sendToContext :: PrimDarcsOption (Maybe AbsolutePath)
- mail :: PrimDarcsOption Bool
- sendmailCmd :: PrimDarcsOption (Maybe String)
- charset :: PrimDarcsOption (Maybe String)
- editDescription :: 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 ResolveConflicts
- reorder :: PrimDarcsOption Reorder
- reorderPush :: PrimDarcsOption Reorder
- data Compression
- compress :: PrimDarcsOption Compression
- usePacks :: PrimDarcsOption Bool
- data WithPatchIndex
- patchIndexNo :: PrimDarcsOption WithPatchIndex
- patchIndexYes :: PrimDarcsOption WithPatchIndex
- data Reorder
- minimize :: PrimDarcsOption Bool
- storeInMemory :: PrimDarcsOption Bool
- data OptimizeDeep
- optimizeDeep :: PrimDarcsOption OptimizeDeep
- data Output
- output :: PrimDarcsOption (Maybe Output)
- data WithSummary
- withSummary :: PrimDarcsOption WithSummary
- maybeSummary :: Maybe WithSummary -> PrimDarcsOption (Maybe WithSummary)
- data RemoteDarcs
- remoteDarcs :: PrimDarcsOption RemoteDarcs
- data UMask
- umask :: PrimDarcsOption UMask
- data SetScriptsExecutable
- setScriptsExecutable :: PrimDarcsOption SetScriptsExecutable
- 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 AbsolutePath -> Maybe AbsolutePath -> a)
- readMarks :: PrimDarcsOption (Maybe AbsolutePath)
- writeMarks :: PrimDarcsOption (Maybe AbsolutePath)
- 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
- data ShrinkFailure
- shrinkFailure :: PrimDarcsOption ShrinkFailure
- 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]
Documentation
type DarcsOption = OptSpec DarcsOptDescr Flag Source #
DarcsOption
instantiates the first two type parameters of OptSpec
to
what we need in darcs.
Instances
data RootAction Source #
Options for darcs iself that act like sub-commands.
Instances
Show RootAction Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> RootAction -> ShowS # show :: RootAction -> String # showList :: [RootAction] -> ShowS # | |
Eq RootAction Source # | |
Defined in Darcs.UI.Options.All (==) :: RootAction -> RootAction -> Bool # (/=) :: RootAction -> RootAction -> Bool # |
data StdCmdAction Source #
Instances
Show StdCmdAction Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> StdCmdAction -> ShowS # show :: StdCmdAction -> String # showList :: [StdCmdAction] -> ShowS # | |
Eq StdCmdAction Source # | |
Defined in Darcs.UI.Options.All (==) :: StdCmdAction -> StdCmdAction -> Bool # (/=) :: StdCmdAction -> StdCmdAction -> Bool # |
Instances
data HooksConfig Source #
HooksConfig | |
|
data HookConfig Source #
preHook :: DarcsOption a (HookConfig -> a) Source #
postHook :: DarcsOption a (HookConfig -> a) Source #
hooks :: DarcsOption a (HooksConfig -> a) Source #
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 #
Instances
Show WantGuiPause Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> WantGuiPause -> ShowS # show :: WantGuiPause -> String # showList :: [WantGuiPause] -> ShowS # | |
YesNo WantGuiPause Source # | |
Defined in Darcs.UI.Options.All yes :: WantGuiPause -> Bool Source # no :: WantGuiPause -> Bool Source # | |
Eq WantGuiPause Source # | |
Defined in Darcs.Repository.Flags (==) :: WantGuiPause -> WantGuiPause -> Bool # (/=) :: WantGuiPause -> WantGuiPause -> Bool # |
module Darcs.UI.Options.Matching
data SelectDeps Source #
Instances
Show SelectDeps Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> SelectDeps -> ShowS # show :: SelectDeps -> String # showList :: [SelectDeps] -> ShowS # | |
Eq SelectDeps Source # | |
Defined in Darcs.UI.Options.All (==) :: SelectDeps -> SelectDeps -> Bool # (/=) :: SelectDeps -> SelectDeps -> Bool # |
newRepo :: PrimDarcsOption (Maybe String) Source #
This option is for when a new repo gets created. Used for clone, convert import, convert darcs-2, and initialize. For clone and initialize it has the same effect as giving the name as a normal argument.
The --repodir
alias is there for compatibility, should be removed eventually.
TODO We need a way to deprecate options / option names.
data RepoCombinator Source #
Instances
Show RepoCombinator Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> RepoCombinator -> ShowS # show :: RepoCombinator -> String # showList :: [RepoCombinator] -> ShowS # | |
Eq RepoCombinator Source # | |
Defined in Darcs.UI.Options.All (==) :: RepoCombinator -> RepoCombinator -> Bool # (/=) :: RepoCombinator -> RepoCombinator -> Bool # |
data WithWorkingDir Source #
Instances
Show WithWorkingDir Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> WithWorkingDir -> ShowS # show :: WithWorkingDir -> String # showList :: [WithWorkingDir] -> ShowS # | |
YesNo WithWorkingDir Source # | |
Defined in Darcs.UI.Options.All yes :: WithWorkingDir -> Bool Source # no :: WithWorkingDir -> Bool Source # | |
Eq WithWorkingDir Source # | |
Defined in Darcs.Repository.Flags (==) :: WithWorkingDir -> WithWorkingDir -> Bool # (/=) :: WithWorkingDir -> WithWorkingDir -> Bool # |
withWorkingDir :: PrimDarcsOption WithWorkingDir Source #
convert, clone, init
data SetDefault Source #
Instances
Show SetDefault Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> SetDefault -> ShowS # show :: SetDefault -> String # showList :: [SetDefault] -> ShowS # | |
Eq SetDefault Source # | |
Defined in Darcs.Repository.Flags (==) :: SetDefault -> SetDefault -> Bool # (/=) :: SetDefault -> SetDefault -> Bool # |
data InheritDefault Source #
Instances
Show InheritDefault Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> InheritDefault -> ShowS # show :: InheritDefault -> String # showList :: [InheritDefault] -> ShowS # | |
YesNo InheritDefault Source # | |
Defined in Darcs.UI.Options.All yes :: InheritDefault -> Bool Source # no :: InheritDefault -> Bool Source # | |
Eq InheritDefault Source # | |
Defined in Darcs.Repository.Flags (==) :: InheritDefault -> InheritDefault -> Bool # (/=) :: InheritDefault -> InheritDefault -> Bool # |
data WithPrefsTemplates Source #
Instances
Show WithPrefsTemplates Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> WithPrefsTemplates -> ShowS # show :: WithPrefsTemplates -> String # showList :: [WithPrefsTemplates] -> ShowS # | |
YesNo WithPrefsTemplates Source # | |
Defined in Darcs.UI.Options.All yes :: WithPrefsTemplates -> Bool Source # no :: WithPrefsTemplates -> Bool Source # | |
Eq WithPrefsTemplates Source # | |
Defined in Darcs.Repository.Flags (==) :: WithPrefsTemplates -> WithPrefsTemplates -> Bool # (/=) :: WithPrefsTemplates -> WithPrefsTemplates -> Bool # |
data AskLongComment Source #
Instances
Show AskLongComment Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> AskLongComment -> ShowS # show :: AskLongComment -> String # showList :: [AskLongComment] -> ShowS # | |
Eq AskLongComment Source # | |
Defined in Darcs.UI.Options.All (==) :: AskLongComment -> AskLongComment -> Bool # (/=) :: AskLongComment -> AskLongComment -> Bool # |
data LookForAdds Source #
Instances
Show LookForAdds Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> LookForAdds -> ShowS # show :: LookForAdds -> String # showList :: [LookForAdds] -> ShowS # | |
YesNo LookForAdds Source # | |
Defined in Darcs.UI.Options.All yes :: LookForAdds -> Bool Source # no :: LookForAdds -> Bool Source # | |
Eq LookForAdds Source # | |
Defined in Darcs.Repository.Flags (==) :: LookForAdds -> LookForAdds -> Bool # (/=) :: LookForAdds -> LookForAdds -> Bool # |
data LookForMoves Source #
Instances
Show LookForMoves Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> LookForMoves -> ShowS # show :: LookForMoves -> String # showList :: [LookForMoves] -> ShowS # | |
YesNo LookForMoves Source # | |
Defined in Darcs.UI.Options.All yes :: LookForMoves -> Bool Source # no :: LookForMoves -> Bool Source # | |
Eq LookForMoves Source # | |
Defined in Darcs.Repository.Flags (==) :: LookForMoves -> LookForMoves -> Bool # (/=) :: LookForMoves -> LookForMoves -> Bool # |
data LookForReplaces Source #
Instances
Show LookForReplaces Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> LookForReplaces -> ShowS # show :: LookForReplaces -> String # showList :: [LookForReplaces] -> ShowS # | |
YesNo LookForReplaces Source # | |
Defined in Darcs.UI.Options.All yes :: LookForReplaces -> Bool Source # no :: LookForReplaces -> Bool Source # | |
Eq LookForReplaces Source # | |
Defined in Darcs.Repository.Flags (==) :: LookForReplaces -> LookForReplaces -> Bool # (/=) :: LookForReplaces -> LookForReplaces -> Bool # |
allowProblematicFilenames :: DarcsOption a (Bool -> Bool -> a) Source #
onlyToFiles :: PrimDarcsOption Bool Source #
TODO: see issue2395
data DiffAlgorithm Source #
Instances
Show DiffAlgorithm Source # | |
Defined in Darcs.Util.Diff showsPrec :: Int -> DiffAlgorithm -> ShowS # show :: DiffAlgorithm -> String # showList :: [DiffAlgorithm] -> ShowS # | |
Eq DiffAlgorithm Source # | |
Defined in Darcs.Util.Diff (==) :: DiffAlgorithm -> DiffAlgorithm -> Bool # (/=) :: DiffAlgorithm -> DiffAlgorithm -> Bool # |
data WithContext Source #
Instances
Show WithContext Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> WithContext -> ShowS # show :: WithContext -> String # showList :: [WithContext] -> ShowS # | |
YesNo WithContext Source # | |
Defined in Darcs.UI.Options.All yes :: WithContext -> Bool Source # no :: WithContext -> Bool Source # | |
Eq WithContext Source # | |
Defined in Darcs.UI.Options.All (==) :: WithContext -> WithContext -> Bool # (/=) :: WithContext -> WithContext -> Bool # |
data ExternalDiff Source #
ExternalDiff | |
|
Instances
Show ExternalDiff Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> ExternalDiff -> ShowS # show :: ExternalDiff -> String # showList :: [ExternalDiff] -> ShowS # | |
Eq ExternalDiff Source # | |
Defined in Darcs.UI.Options.All (==) :: ExternalDiff -> ExternalDiff -> Bool # (/=) :: ExternalDiff -> ExternalDiff -> Bool # |
data TestChanges Source #
Instances
Eq TestChanges Source # | |
Defined in Darcs.UI.Options.All (==) :: TestChanges -> TestChanges -> Bool # (/=) :: TestChanges -> TestChanges -> Bool # |
data LeaveTestDir Source #
Instances
Show LeaveTestDir Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> LeaveTestDir -> ShowS # show :: LeaveTestDir -> String # showList :: [LeaveTestDir] -> ShowS # | |
YesNo LeaveTestDir Source # | |
Defined in Darcs.UI.Options.All yes :: LeaveTestDir -> Bool Source # no :: LeaveTestDir -> Bool Source # | |
Eq LeaveTestDir Source # | |
Defined in Darcs.Repository.Flags (==) :: LeaveTestDir -> LeaveTestDir -> Bool # (/=) :: LeaveTestDir -> LeaveTestDir -> Bool # |
data AllowConflicts Source #
Instances
Show AllowConflicts Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> AllowConflicts -> ShowS # show :: AllowConflicts -> String # showList :: [AllowConflicts] -> ShowS # | |
Eq AllowConflicts Source # | |
Defined in Darcs.Repository.Flags (==) :: AllowConflicts -> AllowConflicts -> Bool # (/=) :: AllowConflicts -> AllowConflicts -> Bool # |
conflictsNo :: PrimDarcsOption (Maybe AllowConflicts) Source #
push, apply, rebase apply: default to NoAllowConflicts
conflictsYes :: PrimDarcsOption (Maybe AllowConflicts) Source #
pull, rebase pull: default to YesAllowConflicts
MarkConflicts
data ResolveConflicts Source #
Instances
Show ResolveConflicts Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> ResolveConflicts -> ShowS # show :: ResolveConflicts -> String # showList :: [ResolveConflicts] -> ShowS # | |
Eq ResolveConflicts Source # | |
Defined in Darcs.Repository.Flags (==) :: ResolveConflicts -> ResolveConflicts -> Bool # (/=) :: ResolveConflicts -> ResolveConflicts -> Bool # |
reorder :: PrimDarcsOption Reorder Source #
pull, apply, rebase pull, rebase apply
reorderPush :: PrimDarcsOption Reorder Source #
push; same as reorder
but with help descriptions swapped
data Compression Source #
Instances
Show Compression Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> Compression -> ShowS # show :: Compression -> String # showList :: [Compression] -> ShowS # | |
YesNo Compression Source # | |
Defined in Darcs.UI.Options.All yes :: Compression -> Bool Source # no :: Compression -> Bool Source # | |
Eq Compression Source # | |
Defined in Darcs.UI.Options.All (==) :: Compression -> Compression -> Bool # (/=) :: Compression -> Compression -> Bool # |
compress :: PrimDarcsOption Compression Source #
push
data WithPatchIndex Source #
Instances
Show WithPatchIndex Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> WithPatchIndex -> ShowS # show :: WithPatchIndex -> String # showList :: [WithPatchIndex] -> ShowS # | |
YesNo WithPatchIndex Source # | |
Defined in Darcs.UI.Options.All yes :: WithPatchIndex -> Bool Source # no :: WithPatchIndex -> Bool Source # | |
Eq WithPatchIndex Source # | |
Defined in Darcs.Repository.Flags (==) :: WithPatchIndex -> WithPatchIndex -> Bool # (/=) :: WithPatchIndex -> WithPatchIndex -> Bool # |
data OptimizeDeep Source #
Instances
Show OptimizeDeep Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> OptimizeDeep -> ShowS # show :: OptimizeDeep -> String # showList :: [OptimizeDeep] -> ShowS # | |
Eq OptimizeDeep Source # | |
Defined in Darcs.Repository.Flags (==) :: OptimizeDeep -> OptimizeDeep -> Bool # (/=) :: OptimizeDeep -> OptimizeDeep -> Bool # |
data WithSummary Source #
Instances
Show WithSummary Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> WithSummary -> ShowS # show :: WithSummary -> String # showList :: [WithSummary] -> ShowS # | |
YesNo WithSummary Source # | |
Defined in Darcs.UI.Options.All yes :: WithSummary -> Bool Source # no :: WithSummary -> Bool Source # | |
Eq WithSummary Source # | |
Defined in Darcs.UI.Options.All (==) :: WithSummary -> WithSummary -> Bool # (/=) :: WithSummary -> WithSummary -> Bool # |
data RemoteDarcs Source #
Instances
Show RemoteDarcs Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> RemoteDarcs -> ShowS # show :: RemoteDarcs -> String # showList :: [RemoteDarcs] -> ShowS # | |
Eq RemoteDarcs Source # | |
Defined in Darcs.Repository.Flags (==) :: RemoteDarcs -> RemoteDarcs -> Bool # (/=) :: RemoteDarcs -> RemoteDarcs -> Bool # |
data SetScriptsExecutable Source #
Instances
Show SetScriptsExecutable Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> SetScriptsExecutable -> ShowS # show :: SetScriptsExecutable -> String # showList :: [SetScriptsExecutable] -> ShowS # | |
YesNo SetScriptsExecutable Source # | |
Defined in Darcs.UI.Options.All yes :: SetScriptsExecutable -> Bool Source # no :: SetScriptsExecutable -> Bool Source # | |
Eq SetScriptsExecutable Source # | |
Defined in Darcs.Repository.Flags (==) :: SetScriptsExecutable -> SetScriptsExecutable -> Bool # (/=) :: SetScriptsExecutable -> SetScriptsExecutable -> Bool # |
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 |
Instances
marks :: DarcsOption a (Maybe AbsolutePath -> Maybe AbsolutePath -> a) Source #
data PatchFormat Source #
Instances
Show PatchFormat Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> PatchFormat -> ShowS # show :: PatchFormat -> String # showList :: [PatchFormat] -> ShowS # | |
Eq PatchFormat Source # | |
Defined in Darcs.Repository.Flags (==) :: PatchFormat -> PatchFormat -> Bool # (/=) :: PatchFormat -> PatchFormat -> Bool # |
hashed :: PrimDarcsOption () Source #
Deprecated flag, still present to output an error message.
data ChangesFormat Source #
Instances
Show ChangesFormat Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> ChangesFormat -> ShowS # show :: ChangesFormat -> String # showList :: [ChangesFormat] -> ShowS # | |
Eq ChangesFormat Source # | |
Defined in Darcs.UI.Options.All (==) :: ChangesFormat -> ChangesFormat -> Bool # (/=) :: ChangesFormat -> ChangesFormat -> Bool # |
data TestStrategy Source #
Instances
Show TestStrategy Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> TestStrategy -> ShowS # show :: TestStrategy -> String # showList :: [TestStrategy] -> ShowS # | |
Eq TestStrategy Source # | |
Defined in Darcs.UI.Options.All (==) :: TestStrategy -> TestStrategy -> Bool # (/=) :: TestStrategy -> TestStrategy -> Bool # |
data ShrinkFailure Source #
Instances
Show ShrinkFailure Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> ShrinkFailure -> ShowS # show :: ShrinkFailure -> String # showList :: [ShrinkFailure] -> ShowS # | |
Eq ShrinkFailure Source # | |
Defined in Darcs.UI.Options.All (==) :: ShrinkFailure -> ShrinkFailure -> Bool # (/=) :: ShrinkFailure -> ShrinkFailure -> Bool # |
data EnumPatches Source #
Instances
Show EnumPatches Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> EnumPatches -> ShowS # show :: EnumPatches -> String # showList :: [EnumPatches] -> ShowS # | |
YesNo EnumPatches Source # | |
Defined in Darcs.UI.Options.All yes :: EnumPatches -> Bool Source # no :: EnumPatches -> Bool Source # | |
Eq EnumPatches Source # | |
Defined in Darcs.UI.Options.All (==) :: EnumPatches -> EnumPatches -> Bool # (/=) :: EnumPatches -> EnumPatches -> Bool # |
data GzcrcsAction Source #
Instances
Show GzcrcsAction Source # | |
Defined in Darcs.UI.Options.All showsPrec :: Int -> GzcrcsAction -> ShowS # show :: GzcrcsAction -> String # showList :: [GzcrcsAction] -> ShowS # | |
Eq GzcrcsAction Source # | |
Defined in Darcs.UI.Options.All (==) :: GzcrcsAction -> GzcrcsAction -> Bool # (/=) :: GzcrcsAction -> GzcrcsAction -> Bool # |