| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Darcs.UI.Commands
- 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 ())
- commandGetArgPossibilities :: 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
- 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 -> Maybe String -> Bool -> Maybe String -> Bool -> 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
 
- getCommandHelp :: Maybe (DarcsCommand pf1) -> DarcsCommand pf2 -> String
- getCommandMiniHelp :: Maybe (DarcsCommand pf1) -> DarcsCommand pf2 -> String
- getSubcommands :: DarcsCommand pf -> [CommandControl]
- usage :: [CommandControl] -> String
- usageHelper :: [CommandControl] -> String
- subusage :: DarcsCommand pf -> String
- 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 ()
- printDryRunMessageAndExit :: (RepoPatch p, ApplyState p ~ Tree) => String -> Verbosity -> Summary -> DryRun -> XmlOutput -> Bool -> FL (PatchInfoAnd p) wX wY -> IO ()
- setEnvDarcsPatches :: (RepoPatch p, ApplyState p ~ Tree) => FL (PatchInfoAnd p) wX wY -> IO ()
- setEnvDarcsFiles :: (PatchInspect p, Patchy p) => p wX wY -> IO ()
- formatPath :: String -> String
- 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
Constructors
| CommandData WrappedCommand | |
| HiddenCommand WrappedCommand | |
| GroupName String | 
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
Constructors
| DarcsCommand | |
| Fields 
 | |
| SuperCommand | |
| Fields 
 | |
data WrappedCommand where Source
A WrappedCommand is a DarcsCommand where the options type has been hidden
Constructors
| 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 -> Maybe String -> Bool -> Maybe String -> Bool -> a) b -> DarcsOption a c Source
disambiguateCommands :: [CommandControl] -> String -> [String] -> Either String (CommandArgs, [String]) Source
data CommandArgs where Source
Constructors
| CommandOnly :: DarcsCommand parsedFlags -> CommandArgs | |
| SuperCommandOnly :: DarcsCommand parsedFlags -> CommandArgs | |
| SuperCommandSub :: DarcsCommand parsedFlags1 -> DarcsCommand parsedFlags2 -> CommandArgs | 
getCommandHelp :: Maybe (DarcsCommand pf1) -> DarcsCommand pf2 -> String Source
getCommandMiniHelp :: Maybe (DarcsCommand pf1) -> DarcsCommand pf2 -> String Source
getSubcommands :: DarcsCommand pf -> [CommandControl] Source
usage :: [CommandControl] -> String Source
usageHelper :: [CommandControl] -> String Source
subusage :: DarcsCommand pf -> String Source
extractCommands :: [CommandControl] -> [WrappedCommand] Source
extractAllCommands :: [CommandControl] -> [WrappedCommand] Source
normalCommand :: DarcsCommand parsedFlags -> CommandControl Source
hiddenCommand :: DarcsCommand parsedFlags -> CommandControl Source
superName :: Maybe (DarcsCommand pf) -> String Source
nodefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String] Source
putVerbose :: [DarcsFlag] -> Doc -> IO () Source
putWarning :: [DarcsFlag] -> Doc -> IO () Source
putVerboseWarning :: [DarcsFlag] -> Doc -> IO () Source
printDryRunMessageAndExit :: (RepoPatch p, ApplyState p ~ Tree) => String -> Verbosity -> Summary -> DryRun -> XmlOutput -> Bool -> FL (PatchInfoAnd p) wX wY -> IO () Source
printDryRunMessageAndExit action flags patches--dry-run option had
 not been passed to darcs. Then darcs exits successfully.  action is the
 name of the action being taken, like "push" flags is the list of flags
 which were sent to darcs patches is the sequence of patches which would be
 touched by action.
setEnvDarcsPatches :: (RepoPatch p, ApplyState p ~ Tree) => 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, Patchy 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.
formatPath :: String -> String Source
Format a path for screen output, so that the user sees where the path begins and ends. Could (should?) also warn about unprintable characters here.
defaultRepo :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String] Source