Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data CommandControl
- data DarcsCommand
- = DarcsCommand {
- commandProgramName, commandName :: String
- commandHelp :: Doc
- commandDescription :: String
- commandExtraArgs :: Int
- commandExtraArgHelp :: [String]
- commandCommand :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
- commandPrereq :: [DarcsFlag] -> IO (Either String ())
- commandCompleteArgs :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO [String]
- commandArgdefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
- commandOptions :: CommandOptions
- | SuperCommand {
- commandProgramName, commandName :: String
- commandHelp :: Doc
- commandDescription :: String
- commandPrereq :: [DarcsFlag] -> IO (Either String ())
- commandSubCommands :: [CommandControl]
- = DarcsCommand {
- commandAlias :: String -> Maybe DarcsCommand -> DarcsCommand -> DarcsCommand
- commandStub :: String -> Doc -> String -> DarcsCommand -> DarcsCommand
- withStdOpts :: DarcsOption (Maybe StdCmdAction -> Verbosity -> b) c -> DarcsOption (UseCache -> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag]) b -> CommandOptions
- commandOptDescr :: AbsolutePath -> DarcsCommand -> [OptDescr DarcsFlag]
- commandAlloptions :: DarcsCommand -> ([DarcsOptDescr DarcsFlag], [DarcsOptDescr DarcsFlag])
- commandDefaults :: DarcsCommand -> [DarcsFlag]
- commandCheckOptions :: DarcsCommand -> [DarcsFlag] -> [OptMsg]
- disambiguateCommands :: [CommandControl] -> String -> [String] -> Either String (CommandArgs, [String])
- data CommandArgs
- getSubcommands :: DarcsCommand -> [CommandControl]
- extractCommands :: [CommandControl] -> [DarcsCommand]
- extractAllCommands :: [CommandControl] -> [DarcsCommand]
- normalCommand :: DarcsCommand -> CommandControl
- hiddenCommand :: DarcsCommand -> CommandControl
- commandGroup :: String -> CommandControl
- superName :: Maybe DarcsCommand -> String
- nodefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
- putInfo :: [DarcsFlag] -> Doc -> IO ()
- putVerbose :: [DarcsFlag] -> Doc -> IO ()
- putWarning :: [DarcsFlag] -> Doc -> IO ()
- putVerboseWarning :: [DarcsFlag] -> Doc -> IO ()
- putFinished :: [DarcsFlag] -> String -> IO ()
- abortRun :: [DarcsFlag] -> Doc -> IO ()
- setEnvDarcsPatches :: RepoPatch p => FL (PatchInfoAnd p) wX wY -> IO ()
- setEnvDarcsFiles :: PatchInspect p => p wX wY -> IO ()
- defaultRepo :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
- amInHashedRepository :: [DarcsFlag] -> IO (Either String ())
- amInRepository :: [DarcsFlag] -> IO (Either String ())
- amNotInRepository :: [DarcsFlag] -> IO (Either String ())
- findRepository :: [DarcsFlag] -> IO (Either String ())
Documentation
data DarcsCommand Source #
A DarcsCommand
represents a command like add, record etc.
DarcsCommand | |
| |
SuperCommand | |
|
commandAlias :: String -> Maybe DarcsCommand -> DarcsCommand -> DarcsCommand Source #
commandStub :: String -> Doc -> String -> DarcsCommand -> DarcsCommand Source #
withStdOpts :: DarcsOption (Maybe StdCmdAction -> Verbosity -> b) c -> DarcsOption (UseCache -> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag]) b -> CommandOptions Source #
Construct CommandOptions
from the command specific basic and advanced
DarcsOption
s
commandOptDescr :: AbsolutePath -> DarcsCommand -> [OptDescr DarcsFlag] Source #
Option descriptions as required by getOpt
,
i.e. resolved with the given AbsolutePath
.
commandAlloptions :: DarcsCommand -> ([DarcsOptDescr DarcsFlag], [DarcsOptDescr DarcsFlag]) Source #
Option descriptions split into basic and advanced options
commandDefaults :: DarcsCommand -> [DarcsFlag] Source #
Built-in default values for all DarcsFlag
s supported by the given
command
commandCheckOptions :: DarcsCommand -> [DarcsFlag] -> [OptMsg] Source #
For the given DarcsCommand
check the given DarcsFlag
s for
consistency
disambiguateCommands :: [CommandControl] -> String -> [String] -> Either String (CommandArgs, [String]) Source #
data CommandArgs Source #
getSubcommands :: DarcsCommand -> [CommandControl] Source #
extractCommands :: [CommandControl] -> [DarcsCommand] Source #
extractAllCommands :: [CommandControl] -> [DarcsCommand] Source #
commandGroup :: String -> CommandControl Source #
nodefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String] Source #
setEnvDarcsPatches :: RepoPatch p => FL (PatchInfoAnd p) wX wY -> IO () Source #
Set the DARCS_PATCHES and DARCS_PATCHES_XML environment variables with info about the given patches, for use in post-hooks.
setEnvDarcsFiles :: PatchInspect p => p wX wY -> IO () Source #
Set the DARCS_FILES environment variable to the files touched by the given patch, one per line, for use in post-hooks.
defaultRepo :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String] Source #
To use for commandArgdefaults field.