Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data CommandControl
- data DarcsCommand parsedFlags
- = DarcsCommand {
- commandProgramName, commandName, commandHelp, commandDescription :: String
- commandExtraArgs :: Int
- commandExtraArgHelp :: [String]
- commandCommand :: (AbsolutePath, AbsolutePath) -> parsedFlags -> [String] -> IO ()
- commandPrereq :: [DarcsFlag] -> IO (Either String ())
- commandCompleteArgs :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO [String]
- commandArgdefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
- commandBasicOptions :: [DarcsOptDescr DarcsFlag]
- commandAdvancedOptions :: [DarcsOptDescr DarcsFlag]
- commandDefaults :: [DarcsFlag]
- commandCheckOptions :: [DarcsFlag] -> [String]
- commandParseOptions :: [DarcsFlag] -> parsedFlags
- | SuperCommand {
- commandProgramName, commandName, commandHelp, commandDescription :: String
- commandPrereq :: [DarcsFlag] -> IO (Either String ())
- commandSubCommands :: [CommandControl]
- = DarcsCommand {
- data WrappedCommand where
- WrappedCommand :: DarcsCommand parsedFlags -> WrappedCommand
- wrappedCommandName :: WrappedCommand -> String
- wrappedCommandDescription :: WrappedCommand -> String
- commandAlias :: String -> Maybe (DarcsCommand pf) -> DarcsCommand pf -> DarcsCommand pf
- commandStub :: String -> String -> String -> DarcsCommand pf -> DarcsCommand pf
- commandOptions :: AbsolutePath -> DarcsCommand pf -> [OptDescr DarcsFlag]
- commandAlloptions :: DarcsCommand pf -> ([DarcsOptDescr DarcsFlag], [DarcsOptDescr DarcsFlag])
- withStdOpts :: DarcsOption (Maybe StdCmdAction -> Bool -> Bool -> Verbosity -> Bool -> b) c -> DarcsOption (UseCache -> HooksConfig -> a) b -> DarcsOption a c
- disambiguateCommands :: [CommandControl] -> String -> [String] -> Either String (CommandArgs, [String])
- data CommandArgs where
- CommandOnly :: DarcsCommand parsedFlags -> CommandArgs
- SuperCommandOnly :: DarcsCommand parsedFlags -> CommandArgs
- SuperCommandSub :: DarcsCommand parsedFlags1 -> DarcsCommand parsedFlags2 -> CommandArgs
- getSubcommands :: DarcsCommand pf -> [CommandControl]
- extractCommands :: [CommandControl] -> [WrappedCommand]
- extractAllCommands :: [CommandControl] -> [WrappedCommand]
- normalCommand :: DarcsCommand parsedFlags -> CommandControl
- hiddenCommand :: DarcsCommand parsedFlags -> CommandControl
- commandGroup :: String -> CommandControl
- superName :: Maybe (DarcsCommand pf) -> String
- nodefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
- putInfo :: [DarcsFlag] -> Doc -> IO ()
- putVerbose :: [DarcsFlag] -> Doc -> IO ()
- putWarning :: [DarcsFlag] -> Doc -> IO ()
- putVerboseWarning :: [DarcsFlag] -> Doc -> IO ()
- abortRun :: [DarcsFlag] -> Doc -> IO ()
- setEnvDarcsPatches :: (RepoPatch p, ApplyState p ~ Tree) => FL (PatchInfoAnd rt 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 CommandControl Source #
data DarcsCommand parsedFlags Source #
A DarcsCommand
represents a command like add, record etc.
The parsedFlags
type represents the options that are
passed to the command's implementation
DarcsCommand | |
| |
SuperCommand | |
|
data WrappedCommand where Source #
A WrappedCommand
is a DarcsCommand
where the options type has been hidden
WrappedCommand :: DarcsCommand parsedFlags -> WrappedCommand |
commandAlias :: String -> Maybe (DarcsCommand pf) -> DarcsCommand pf -> DarcsCommand pf Source #
commandStub :: String -> String -> String -> DarcsCommand pf -> DarcsCommand pf Source #
commandOptions :: AbsolutePath -> DarcsCommand pf -> [OptDescr DarcsFlag] Source #
commandAlloptions :: DarcsCommand pf -> ([DarcsOptDescr DarcsFlag], [DarcsOptDescr DarcsFlag]) Source #
withStdOpts :: DarcsOption (Maybe StdCmdAction -> Bool -> Bool -> Verbosity -> Bool -> b) c -> DarcsOption (UseCache -> HooksConfig -> a) b -> DarcsOption a c Source #
disambiguateCommands :: [CommandControl] -> String -> [String] -> Either String (CommandArgs, [String]) Source #
data CommandArgs where Source #
CommandOnly :: DarcsCommand parsedFlags -> CommandArgs | |
SuperCommandOnly :: DarcsCommand parsedFlags -> CommandArgs | |
SuperCommandSub :: DarcsCommand parsedFlags1 -> DarcsCommand parsedFlags2 -> CommandArgs |
getSubcommands :: DarcsCommand pf -> [CommandControl] Source #
extractCommands :: [CommandControl] -> [WrappedCommand] Source #
extractAllCommands :: [CommandControl] -> [WrappedCommand] Source #
normalCommand :: DarcsCommand parsedFlags -> CommandControl Source #
DarcsCommand parsedFlags -> CommandControl Source #
::commandGroup :: String -> CommandControl Source #
nodefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String] Source #
setEnvDarcsPatches :: (RepoPatch p, ApplyState p ~ Tree) => FL (PatchInfoAnd rt 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 #