File compleat-1.0+git.20220402.ec8fccc.obscpio of Package compleat

07070100000000000081A40000000000000000000000016248715500000030000000000000000000000000000000000000002D00000000compleat-1.0+git.20220402.ec8fccc/.gitignore*.o
*.hi
compleat
dist
README.html
.stack-work/
07070100000001000081A40000000000000000000000016248715500000CE3000000000000000000000000000000000000002F00000000compleat-1.0+git.20220402.ec8fccc/Completer.hsmodule Completer
    ( Completer, run
    , continue, optional, skip
    , (<|>), (-->)
    , str, shellCommand
    , many, many1
    ) where
import Control.Monad (liftM, sequence)
import Data.List (isPrefixOf)
import GHC.IO.Handle (hGetContents)
import System.Directory (getDirectoryContents)
import System.Posix.Env (setEnv)
import System.Process (StdStream(CreatePipe), createProcess, proc, std_out)

-- The "Completer" type is a function that takes a list of input tokens and
-- returns a list of possible completions.  Each completion can be a new list
-- of tokens (which will be handed to the next completer in a sequence) or
-- an action to generate a list of strings.
--
-- This module provides a set of primitive completers, and combinators to build
-- new completers through alternation, repetition, and sequencing.  These are
-- essentially identical to the parser combinators in "Monadic Parsing" by Hutton
-- and Meijer, except that they short-circuit: if all of the input is consumed by
-- one completer in a sequence, then the sequence returns the results of that
-- completer, rather than failure.

type Completer = [String] -> [Completion]
data Completion = Tokens [String] | Suggestions (IO [String])

run :: Completer -> [String] -> IO [String]
run c ts = liftM concat $ sequence [x | Suggestions x <- c ts]

-- Shell commands

shellCommand :: String -> Completer
shellCommand command = match (const True) (\t -> do
    setEnv "COMP_CWORD" t True
    output <- getCommandOutput command
    return $ matchesFrom (lines output) t)

getCommandOutput :: String -> IO String
getCommandOutput command = do
    (_, Just hout, _, _) <- createProcess (proc "bash" ["-c", command])
                                          {std_out = CreatePipe}
    hGetContents hout

-- Matching

-- Match or suggest the specified string.
str :: String -> Completer
str s = match (s ==) (\t -> return $ matchesFrom [s] t)

-- Build a completer that looks at a single token. If more input remains then call
-- predicate "p" to decide whether to continue.  Otherwise, call fuction "suggest"
-- to generate a list of completions.
match :: (String -> Bool) -> (String -> IO [String]) -> Completer
match p suggest ts = case ts of
    []     -> []
    [t]    -> [Suggestions $ suggest t]
    (t:ts) -> if p t then continue ts else []

escape :: String -> String
escape = concatMap escape'
    where escape' ':' = "\\:"
          escape' c = [c]

-- Return words 
matchesFrom :: [String] -> String -> [String]
matchesFrom xs t = [(escape x) ++ " " | x <- xs, t `isPrefixOf` x]

-- Other primitives

-- Consume nothing.
continue :: Completer
continue ts = [Tokens ts]

-- Consume anything.
skip :: Completer
skip (t:ts) = [Tokens ts]
skip _      = []


-- Combinators

optional :: Completer -> Completer
optional c = c <|> continue

-- Choice operator.
(<|>) :: Completer -> Completer -> Completer
c <|> d = \ts -> c ts ++ d ts

-- Sequence operator.
(-->) :: Completer -> Completer -> Completer
c --> d = \ts -> concat [ case result of
                            Tokens ts' -> d ts'
                            _          -> [result]
                        | result <- c ts]

-- Repetition.
many :: Completer -> Completer
many p = many1 p <|> continue

many1 :: Completer -> Completer
many1 p = p --> many p
07070100000002000081A4000000000000000000000001624871550000012F000000000000000000000000000000000000002B00000000compleat-1.0+git.20220402.ec8fccc/Makefilebuild:
	stack build
.PHONY: build

install: build
	stack install
	install -d ~/.bash_completion.d
	install -m 0644 compleat_setup ~/.bash_completion.d
.PHONY: install

install-fish: build
	stack install
	install -d ~/.config/fish
	install -m 0644 compleat_setup.fish ~/.config/fish
.PHONY: install-fish
07070100000003000081A40000000000000000000000016248715500001421000000000000000000000000000000000000003200000000compleat-1.0+git.20220402.ec8fccc/README.markdownCompleat
========

Generate tab completion for any shell command by specifying its usage in a
familiar manpage-like format.  For example, a usage specification for
`top(1)`:

    top [-b | -c | -H | -i | -s | -S | -d <delay> | -n <num> | -p <pid> ...] ... ;
    top (-h|-v)

Supported shells are `bash`, `fish`, and `zsh`.

Installation
------------

Get the source code: `git clone git://github.com/mbrubeck/compleat.git`

Next, install [Stack][stack].

To install Compleat in your system, run:

    make install

This will install the `compleat` binary into `~/.local/bin` and the
`compleat_setup` script into `~/.bash_completion.d`.

### bash

To enable compleat in bash, add the following line to your `.bashrc`.
(Adjust the path if you configured with a custom prefix.)

    source ~/.bash_completion.d/compleat_setup

and install your .usage files in a directory named `/etc/compleat.d` or
`~/.compleat`:

    mkdir ~/compleat
    cp examples/* ~/compleat

Restart your shell to begin using completions:

    exec bash

### zsh

zsh support requires zsh >= 4.2.1, and currently uses zsh's bash-compatibility
mode rather than taking advantage of zsh's extended completion features.

To enable compleat in zsh, make the following change to your `.zshrc`.
(Adjust the path if you configured with a custom prefix.)

If you used the zsh wizard (zsh-newuser-install) to set up your `zshrc`, it should contain lines
like the following (if they don't exist, simply add the lines in the change below):

    autoload -Uz compinit
    compinit

Change these to:

    autoload -Uz compinit bashcompinit
    compinit
    bashcompinit

    source ~/.bash_completion.d/compleat_setup

and install your .usage files in a directory named `/etc/compleat.d` or
`~/.compleat`:

    sudo mkdir /etc/compleat.d
    sudo cp examples/* /etc/compleat.d

Restart your shell to begin using completions:

    exec zsh

### fish

To install the fish completion file, run:

    make install-fish

To enable compleat in fish, add the following line to your `~/.config/fish/config.fish`.

    source ~/.config/fish/compleat_setup.fish

and install your .usage files in a directory named `/etc/compleat.d` or
`~/.compleat`:

    mkdir ~/compleat
    cp examples/* ~/compleat

Restart your shell to begin using completions:

    exec fish

### Testing

Type `top` and then press Tab a few times to see the example files in action.

Syntax
------

A usage file contains commands and definitions, separated by semicolons.

A *command* consists of a *command name* followed by a *pattern*.  The command
name can be any atom.  If there is more than one command in the file, compleat
will attempt to match each of them against the input line.

An *atom* consists of letters, numbers, and any of the characters `-_/@=+.,:`,
or any string enclosed in double quotes with C/Java-style backslash escapes.

The following are valid patterns:

* Any atom matches itself: `foo` matches the string `foo`.  `"x\\y"` matches
  the string `x\y`.
* `a b` matches `a` followed by `b`.
* `a b | c` matches either `a b` or `c`.
* `[a]` matches zero or one occurrences of `a`.
* `a ...` matches one or more occurrences of `a`.
* `[a] ...` matches zero or more occurrences of `a`.

Use parentheses to group patterns:

* `a (b | c)` matches `a` followed by either `b` or `c`.
* `(a | b) ...` matches `a` or `b` followed by any number of additional
  `a` or `b`.

Patterns may also include *variables*:

* `name = value;` defines a new variable.  The name can be any atom,
  and the value can be any pattern.  Then `<name>` in a pattern refers to the
  value as a sub-pattern.

* `name = !command;` defines a variable that uses a shell command to
  generate suggested completions.  The shell command should print one
  suggested completion per line.  The `$COMP_LINE` and `$COMP_CWORD`
  environment will contain the input line and the current word being
  completed.

* If no value is defined for `name`, then the pattern `<name>` will match any
  word.

Copyright
---------

Copyright (c) 2009 Matt Brubeck

Permission is hereby granted, free of charge, to any person
obtaining a copy of this software and associated documentation
files (the "Software"), to deal in the Software without
restriction, including without limitation the rights to use,
copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the
Software is furnished to do so, subject to the following
conditions:

The above copyright notice and this permission notice shall be
included in all copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
OTHER DEALINGS IN THE SOFTWARE.


[stack]: https://docs.haskellstack.org/en/stable/README/#how-to-install
07070100000004000081ED000000000000000000000001624871550000004D000000000000000000000000000000000000002C00000000compleat-1.0+git.20220402.ec8fccc/Setup.lhs#!/usr/bin/env runhaskell

> import Distribution.Simple
> main = defaultMain
07070100000005000081A4000000000000000000000001624871550000014A000000000000000000000000000000000000002B00000000compleat-1.0+git.20220402.ec8fccc/TODO.txtSupport:
  Debian/Ubuntu packages.
  Support non-bash shells.
  More examples.
Built-in completers:
  Better filename completer (or just use "complete -o default"?).
  Generic completer for short/long --options.
  Easy way to define new Haskell completers.
    Maybe usage files should be compiled to Haskell or another language?
07070100000006000081A40000000000000000000000016248715500000493000000000000000000000000000000000000002E00000000compleat-1.0+git.20220402.ec8fccc/Tokenize.hsmodule Tokenize (tokenize, tokens, token) where

import Data.Char (isSpace)
import Text.ParserCombinators.Parsec hiding (token, tokens)

-- | @tokenize@
-- Split a shell command into a list of words, attempting to use the same
-- rules as the shell (does not yet handle certain cases like subshells).
-- The command might be incomplete, so handle unbalanced quotes, and treat
-- trailing whitespace as the start of an empty token.

tokenize :: String -> [String]
tokenize s = case runParser tokens () "" s of
                Right ts -> ts
                Left  _  -> []

tokens :: Parser [String]
tokens = do
    ts <- many (try token)
    last <- option [] (many1 space >> return [""])
    return (ts ++ last)

token = spaces >> (quoted '"' <|> quoted '\'' <|> unquoted)

quoted :: Char -> Parser String
quoted q = do
    char q
    manyTill (escaped <|> anyChar) (try (char q >> return ()) <|> eof)

unquoted :: Parser String
unquoted = many1 (escaped <|> satisfy (not . isSpace))

escaped :: Parser Char
escaped = do
    char '\\'
    c <- anyChar
    case c of
        't' -> return '\t'
        'n' -> return '\n'
        'r' -> return '\r'
        _   -> return c
07070100000007000081A40000000000000000000000016248715500000CB7000000000000000000000000000000000000002B00000000compleat-1.0+git.20220402.ec8fccc/Usage.hsmodule Usage (Environment, commands, fromFile, lookupCommand) where

import qualified Completer as C
import Data.List (nub, sort)
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Language (javaStyle)
import qualified Text.ParserCombinators.Parsec.Token as T

-- This module parses the usage file format (see README for an explanation)
-- and generates a Completer (see the Completer module).

data Usage =  Var String
             | Choice [Usage] | Sequence [Usage]
             | Many Usage | Many1 Usage | Optional Usage
             | ShellCommand String
             | Str String
             | Skip

fromFile :: String -> IO Environment
fromFile fileName = do
    result <- parseFromFile usage fileName
    case result of
        Right env -> return env
        Left err  -> error (show err)

-- Evaluator

type Environment = [(EnvName,Usage)] -- Associates variables with values.
data EnvName = VarName String | CommandName String
    deriving Eq

lookupCommand :: Environment -> String -> C.Completer
lookupCommand env command = eval env (main env)
    where main env = Choice $ map snd $ filter ((CommandName command ==) . fst) env

eval :: Environment -> Usage -> C.Completer
eval env (Choice xs)   = foldl1 (C.<|>) (map (eval env) xs)
eval env (Sequence xs) = foldl1 (C.-->) (map (eval env) xs)
eval env (Many x)      = C.many     (eval env x)
eval env (Many1 x)     = C.many1    (eval env x)
eval env (Optional x)  = C.optional (eval env x)
eval env (ShellCommand s) = C.shellCommand s
eval env (Str s)       = C.str s
eval env Skip          = C.skip
eval env (Var s)       = case lookup (VarName s) env of
                            Just u  -> eval env u
                            Nothing -> C.skip

commands :: Environment -> [String]
commands env = nub $ sort [s | (CommandName s, _) <- env]

-- Top-level parser

usage :: Parser Environment
usage = whiteSpace >> sepEndBy1 (try varDef <|> commandDef) (symbol ";")

varDef :: Parser (EnvName, Usage)
varDef = do
    s <- atom
    symbol "="
    u <- shellCommand <|> pattern
    return (VarName s, u)

commandDef :: Parser (EnvName, Usage)
commandDef = do
    s <- atom
    u <- pattern
    return (CommandName s, Sequence [Skip, u])

-- Usage parser

shellCommand = do
    symbol "!"
    s <- many1 (noneOf ";")
    return (ShellCommand s)

pattern = do
    xs <- sepBy1 terms (symbol "|")
    return (Choice xs)

terms = do
    xs <- many1 term
    return (Sequence xs)

term = repeated (group <|> str <|> variable) Many1 id
   <|> repeated optionGroup Many Optional

group = parens pattern
optionGroup = brackets pattern

str = do
    s <- atom
    return $ Str s

variable = do
    s <- between (symbol "<") (symbol ">") atom
    return (Var s)

repeated :: Parser a -> (a -> b) -> (a -> b) -> Parser b
repeated p f g = p >>= \x ->
    try (symbol "..." >> return (f x)) <|> return (g x)

atom :: Parser String
atom = stringLiteral <|> lexeme (many1 (alphaNum <|> oneOf "-_/@=+.,:"))

-- Lexer

lexer :: T.TokenParser ()
lexer  = T.makeTokenParser javaStyle

lexeme        = T.lexeme lexer
symbol        = T.symbol lexer
parens        = T.parens lexer
brackets      = T.brackets lexer
stringLiteral = T.stringLiteral lexer
whiteSpace    = T.whiteSpace lexer
07070100000008000081A40000000000000000000000016248715500000281000000000000000000000000000000000000003100000000compleat-1.0+git.20220402.ec8fccc/compleat.cabalName:                compleat
Version:             1.0
Description:         Generate command-line completions from simple usage descriptions.
License:             MIT
License-file:        README.markdown
Author:              Matt Brubeck
Maintainer:          mbrubeck@limpet.net
Build-Type:          Simple
Cabal-Version:       >=1.2

Data-Files:          compleat_setup

Executable compleat
  Main-Is:           compleat.hs
  Other-Modules:     Completer,
                     Tokenize,
                     Usage
  Build-Depends:     base >= 3 && < 5,
                     parsec >= 2 && < 4,
                     directory, process, unix
07070100000009000081A40000000000000000000000016248715500000515000000000000000000000000000000000000002E00000000compleat-1.0+git.20220402.ec8fccc/compleat.hsimport Completer (run)
import Numeric (readDec)
import System.Environment (getEnv, getArgs, lookupEnv)
import Tokenize (tokenize)
import Usage (Environment, commands, fromFile, lookupCommand)

-- Parse the usage file from the first argument.  If there is a second argument,
-- it is a command-name; find the usage rules for that command and use them to
-- complete the input line.  Otherwise, list all command names in the usage file.
main = do
    args <- getArgs
    env <- fromFile (head args)
    if length args > 1
        then completeLine env (args !! 1)
        else listCommands env

completeLine :: Environment -> String -> IO ()
completeLine env command = do
    line <- getInput
    let completer = lookupCommand env command
    suggestions <- run completer (tokenize line)
    is_fish <- lookupEnv "COMPLEAT_IS_FISH"
    case is_fish of
        Nothing -> mapM_ putStrLn suggestions
        _ -> do
            -- The trailing space must be removed in fish
            let suggestions' = map init suggestions
            mapM_ putStrLn suggestions'

getInput :: IO String
getInput = do
    line  <- getEnv "COMP_LINE"
    point <- getEnv "COMP_POINT"
    let [(n,[])] = readDec point
    return (take n line)

listCommands :: Environment -> IO ()
listCommands = mapM_ putStrLn . commands
0707010000000A000081A400000000000000000000000162487155000002CB000000000000000000000000000000000000003100000000compleat-1.0+git.20220402.ec8fccc/compleat_setup# wrapper needed for zsh (and harmless in bash)
_run_compleat() {
    export COMP_POINT COMP_CWORD COMP_WORDS COMPREPLY BASH_VERSINFO COMP_LINE
    compleat $@
}

[ -n "$COMPLEAT_VENDOR_DIR" ] || COMPLEAT_SYSTEM_DIR=/usr/share/compleat.d
[ -n "$COMPLEAT_SYSTEM_DIR" ] || COMPLEAT_SYSTEM_DIR=/etc/compleat.d
[ -n "$COMPLEAT_USER_DIR"   ] || COMPLEAT_USER_DIR=$HOME/.compleat

for DIR in $COMPLEAT_VENDOR_DIR $COMPLEAT_SYSTEM_DIR $COMPLEAT_USER_DIR; do
    if [ -d $DIR -a -r $DIR -a -x $DIR ]; then
        for FILE in $DIR/*.usage; do
            for COMMAND in `compleat $FILE`; do
                complete -o nospace -o default -C "_run_compleat $FILE $COMMAND" $COMMAND
            done
        done
    fi
done
0707010000000B000081A400000000000000000000000162487155000002AA000000000000000000000000000000000000003600000000compleat-1.0+git.20220402.ec8fccc/compleat_setup.fishfunction _run_compleat
    set -x COMP_LINE (commandline)
    set -x COMP_POINT (commandline -C)
    set -x COMPLEAT_IS_FISH ""
    compleat $argv
end

[ -n "$COMPLEAT_VENDOR_DIR" ]; or set COMPLEAT_SYSTEM_DIR /usr/share/compleat.d
[ -n "$COMPLEAT_SYSTEM_DIR" ]; or set COMPLEAT_SYSTEM_DIR /etc/compleat.d
[ -n "$COMPLEAT_USER_DIR"   ]; or set COMPLEAT_USER_DIR $HOME/.compleat

for DIR in $COMPLEAT_VENDOR_DIR $COMPLEAT_SYSTEM_DIR $COMPLEAT_USER_DIR
    if [ -d $DIR -a -r $DIR -a -x $DIR ]
        for FILE in $DIR/*.usage
            for COMMAND in (compleat $FILE)
                complete -c $COMMAND -a "(_run_compleat $FILE $COMMAND)"
            end
        end
    end
end
0707010000000C000041ED0000000000000000000000026248715500000000000000000000000000000000000000000000002B00000000compleat-1.0+git.20220402.ec8fccc/examples0707010000000D000081A4000000000000000000000001624871550000026A000000000000000000000000000000000000003900000000compleat-1.0+git.20220402.ec8fccc/examples/android.usageandroid <options>
  ( list [avd|target]
  | create avd ( --target <target> | --name <name> | --skin <name> | --path <file>
               | --sdcard <file> | --force ) ...
  | move avd (--name <avd> | --rename <name> | --path <file>) ...
  | (delete|update) avd --name <avd>
  | create project ((--package|--name|--activity|--path) <val> | --target <target>) ...
  | update project ((--name|--path) <val> | --target <target>) ...
  | update adb );

android --help;

options = [--silent | --verbose];
avd = ! android list avd | grep 'Name:' | cut -f2 -d: ;
target = ! android list target | grep '^id:'| cut -f2 -d' ' ;
0707010000000E000081A400000000000000000000000162487155000000C0000000000000000000000000000000000000003700000000compleat-1.0+git.20220402.ec8fccc/examples/cabal.usageSetup.lhs
	  configure [[--help | --verbose | --builddir | --prefix=<DIR> | --user |
	  --global | --docdir=<DIR> | --enable-optimization |
	  --disable-optimization] ...]
	| build
	| install
0707010000000F000081A40000000000000000000000016248715500005B24000000000000000000000000000000000000003700000000compleat-1.0+git.20220402.ec8fccc/examples/darcs.usageDARCS_COMMAND = (help | add | remove | move | replace | revert | unrevert | whatsnew | record | unrecord | amend-record | mark-conflicts | tag | setpref | diff | changes | annotate | dist | trackdown | show | pull | obliterate | rollback | push | send | apply | get | put | initialize | optimize | check | repair | convert);
darcs help ( ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [<DARCS_COMMAND> [DARCS_SUBCOMMAND]]  ;
darcs add ( --boring | ( --case-ok | --reserved-ok ) | ( ( -r | --recursive ) | --not-recursive ) | ( --date-trick | --no-date-trick ) | --repodir <DIRECTORY> | --dry-run | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... ( <FILE> | <DIRECTORY> )...;
darcs remove ( --repodir <DIRECTORY> | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... ( <FILE> | <DIRECTORY> )...;
darcs move ( ( --case-ok | --reserved-ok ) | --repodir <DIRECTORY> | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... <SOURCE> ... <DESTINATION>;
darcs replace ( --token-chars <"[CHARS]"> | ( ( -f | --force ) | --no-force ) | --repodir <DIRECTORY> | --ignore-times | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... <OLD> <NEW> <FILE> ...;
darcs revert ( ( ( -a | --all ) | ( -i | --interactive ) ) | --repodir <DIRECTORY> | --ignore-times | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [ ( <FILE> | <DIRECTORY> ) ]...;
darcs unrevert ( --ignore-times | ( ( -a | --all ) | ( -i | --interactive ) ) | --repodir <DIRECTORY> | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... ;
darcs whatsnew ( ( ( -s | --summary ) | --no-summary ) | ( -u | --unified ) | ( ( -l | --look-for-adds ) | --dont-look-for-adds ) | --repodir <DIRECTORY> | --ignore-times | --boring | --no-cache | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [ ( <FILE> | <DIRECTORY> ) ]...;
darcs record ( ( -m <PATCHNAME> | --patch-name <PATCHNAME> ) | ( -A <EMAIL> | --author <EMAIL> ) | ( --no-test | --test ) | ( --leave-test-directory | --remove-test-directory ) | ( ( -a | --all ) | --pipe | ( -i | --interactive ) ) | ( --ask-deps | --no-ask-deps ) | ( --edit-long-comment | --skip-long-comment | --prompt-long-comment ) | ( ( -l | --look-for-adds ) | --dont-look-for-adds ) | --repodir <DIRECTORY> | --logfile <FILE> | --delete-logfile | ( --compress | --dont-compress ) | --ignore-times | --umask <UMASK> | ( --set-scripts-executable | --dont-set-scripts-executable ) | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [ ( <FILE> | <DIRECTORY> ) ]...;
darcs unrecord ( ( --from-match <PATTERN> | --from-patch <REGEXP> | --from-tag <REGEXP> | --last <NUMBER> | --matches <PATTERN> | ( -p <REGEXP> | --patches <REGEXP> ) | ( -t <REGEXP> | --tags <REGEXP> ) ) | ( --no-deps | --dont-prompt-for-dependencies | --prompt-for-dependencies ) | ( ( -a | --all ) | ( -i | --interactive ) ) | --repodir <DIRECTORY> | ( --compress | --dont-compress ) | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... ;
darcs amend-record ( ( --match <PATTERN> | ( -p <REGEXP> | --patch <REGEXP> ) | ( -n <N> | --index <N> ) ) | ( --no-test | --test ) | ( --leave-test-directory | --remove-test-directory ) | ( ( -a | --all ) | ( -i | --interactive ) ) | ( -A <EMAIL> | --author <EMAIL> ) | ( -m <PATCHNAME> | --patch-name <PATCHNAME> ) | ( --edit-long-comment | --skip-long-comment | --prompt-long-comment ) | ( ( -l | --look-for-adds ) | --dont-look-for-adds ) | --repodir <DIRECTORY> | ( --compress | --dont-compress ) | --ignore-times | --umask <UMASK> | ( --set-scripts-executable | --dont-set-scripts-executable ) | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [ ( <FILE> | <DIRECTORY> ) ]...;
darcs mark-conflicts ( --ignore-times | --repodir <DIRECTORY> | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... ;
darcs tag ( ( -m <PATCHNAME> | --patch-name <PATCHNAME> ) | ( -A <EMAIL> | --author <EMAIL> ) | ( --pipe | ( -i | --interactive ) ) | ( --edit-long-comment | --skip-long-comment | --prompt-long-comment ) | --repodir <DIRECTORY> | ( --compress | --dont-compress ) | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [TAGNAME];
darcs setpref ( --repodir <DIRECTORY> | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... <PREF> <VALUE>;
darcs diff ( ( --to-match <PATTERN> | --to-patch <REGEXP> | --to-tag <REGEXP> | --from-match <PATTERN> | --from-patch <REGEXP> | --from-tag <REGEXP> | --match <PATTERN> | ( -p <REGEXP> | --patch <REGEXP> ) | --last <NUMBER> | ( -n <N-M> | --index <N-M> ) ) | --diff-command <COMMAND> | --diff-opts <OPTIONS> | ( -u | --unified ) | --repodir <DIRECTORY> | --store-in-memory | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [ ( <FILE> | <DIRECTORY> ) ]...;
darcs changes ( ( --to-match <PATTERN> | --to-patch <REGEXP> | --to-tag <REGEXP> | --from-match <PATTERN> | --from-patch <REGEXP> | --from-tag <REGEXP> | --last <NUMBER> | ( -n <N-M> | --index <N-M> ) | --matches <PATTERN> | ( -p <REGEXP> | --patches <REGEXP> ) | ( -t <REGEXP> | --tags <REGEXP> ) ) | --max-count <NUMBER> | --only-to-files | ( --context | --xml-output | --human-readable | --number | --count ) | ( ( -s | --summary ) | --no-summary ) | --reverse | --repo <URL> | --repodir <DIRECTORY> | ( ( -a | --all ) | ( -i | --interactive ) ) | ( --ssh-cm | --no-ssh-cm ) | ( --http-pipelining | --no-http-pipelining ) | --no-cache | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [ ( <FILE> | <DIRECTORY> ) ]...;
darcs annotate ( ( ( -s | --summary ) | --no-summary ) | ( -u | --unified ) | --human-readable | --xml-output | ( --match <PATTERN> | ( -p <REGEXP> | --patch <REGEXP> ) | ( -t <REGEXP> | --tag <REGEXP> ) | ( -n <N> | --index <N> ) ) | --creator-hash <HASH> | --repodir <DIRECTORY> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [ ( <FILE> | <DIRECTORY> ) ]...;
darcs dist ( ( -d <DISTNAME> | --dist-name <DISTNAME> ) | --repodir <DIRECTORY> | ( --match <PATTERN> | ( -p <REGEXP> | --patch <REGEXP> ) | ( -t <REGEXP> | --tag <REGEXP> ) | ( -n <N> | --index <N> ) ) | --store-in-memory | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... ;
darcs trackdown ( --repodir <DIRECTORY> | ( --set-scripts-executable | --dont-set-scripts-executable ) | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [[INITIALIZATION] COMMAND];
darcs show ( contents ( ( --match <PATTERN> | ( -p <REGEXP> | --patch <REGEXP> ) | ( -t <REGEXP> | --tag <REGEXP> ) | ( -n <N> | --index <N> ) ) | --repodir <DIRECTORY> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [FILE]... | files ( ( --files | --no-files ) | ( --directories | --no-directories ) | ( --pending | --no-pending ) | ( -0 | --null ) | --repodir <DIRECTORY> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ...  | index ( ( --files | --no-files ) | ( --directories | --no-directories ) | ( -0 | --null ) | --repodir <DIRECTORY> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ...  | pristine ( ( --files | --no-files ) | ( --directories | --no-directories ) | ( -0 | --null ) | --repodir <DIRECTORY> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ...  | repo ( --repodir <DIRECTORY> | ( --files | --no-files ) | --xml-output | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ...  | authors ( --repodir <DIRECTORY> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ...  | tags ( --repodir <DIRECTORY> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ...  );
darcs pull ( ( --matches <PATTERN> | ( -p <REGEXP> | --patches <REGEXP> ) | ( -t <REGEXP> | --tags <REGEXP> ) ) | ( ( -a | --all ) | ( -i | --interactive ) ) | ( --mark-conflicts | --allow-conflicts | --dont-allow-conflicts | --skip-conflicts ) | --external-merge <COMMAND> | ( --test | --no-test ) | --dry-run | --xml-output | ( ( -s | --summary ) | --no-summary ) | ( --no-deps | --dont-prompt-for-dependencies | --prompt-for-dependencies ) | ( --set-default | --no-set-default ) | --repodir <DIRECTORY> | --ignore-unrelated-repos | ( --intersection | --union | --complement ) | ( --compress | --dont-compress ) | --nolinks | --ignore-times | --remote-repo <URL> | ( --set-scripts-executable | --dont-set-scripts-executable ) | --umask <UMASK> | ( --restrict-paths | --dont-restrict-paths ) | ( --ssh-cm | --no-ssh-cm ) | ( --http-pipelining | --no-http-pipelining ) | --no-cache | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [REPOSITORY]...;
darcs obliterate ( ( --from-match <PATTERN> | --from-patch <REGEXP> | --from-tag <REGEXP> | --last <NUMBER> | --matches <PATTERN> | ( -p <REGEXP> | --patches <REGEXP> ) | ( -t <REGEXP> | --tags <REGEXP> ) ) | ( --no-deps | --dont-prompt-for-dependencies | --prompt-for-dependencies ) | ( ( -a | --all ) | ( -i | --interactive ) ) | --repodir <DIRECTORY> | ( ( -s | --summary ) | --no-summary ) | ( --compress | --dont-compress ) | --ignore-times | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... ;
darcs rollback ( ( --from-match <PATTERN> | --from-patch <REGEXP> | --from-tag <REGEXP> | --last <NUMBER> | --matches <PATTERN> | ( -p <REGEXP> | --patches <REGEXP> ) | ( -t <REGEXP> | --tags <REGEXP> ) ) | ( ( -a | --all ) | ( -i | --interactive ) ) | ( -A <EMAIL> | --author <EMAIL> ) | ( -m <PATCHNAME> | --patch-name <PATCHNAME> ) | ( --edit-long-comment | --skip-long-comment | --prompt-long-comment ) | ( --no-test | --test ) | ( --leave-test-directory | --remove-test-directory ) | --repodir <DIRECTORY> | ( --compress | --dont-compress ) | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [ ( <FILE> | <DIRECTORY> ) ]...;
darcs push ( ( --matches <PATTERN> | ( -p <REGEXP> | --patches <REGEXP> ) | ( -t <REGEXP> | --tags <REGEXP> ) ) | ( --no-deps | --dont-prompt-for-dependencies | --prompt-for-dependencies ) | ( ( -a | --all ) | ( -i | --interactive ) ) | ( --sign | --sign-as <KEYID> | --sign-ssl <IDFILE> | --dont-sign ) | --dry-run | --xml-output | ( ( -s | --summary ) | --no-summary ) | --repodir <DIRECTORY> | ( --set-default | --no-set-default ) | --ignore-unrelated-repos | ( --apply-as <USERNAME> | --apply-as-myself ) | --nolinks | --remote-repo <URL> | ( --ssh-cm | --no-ssh-cm ) | ( --http-pipelining | --no-http-pipelining ) | --no-cache | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [REPOSITORY];
darcs send ( ( --matches <PATTERN> | ( -p <REGEXP> | --patches <REGEXP> ) | ( -t <REGEXP> | --tags <REGEXP> ) ) | ( --no-deps | --dont-prompt-for-dependencies | --prompt-for-dependencies ) | ( ( -a | --all ) | ( -i | --interactive ) ) | --from <EMAIL> | ( -A <EMAIL> | --author <EMAIL> ) | --to <EMAIL> | --cc <EMAIL> | --subject <SUBJECT> | --in-reply-to <EMAIL> | ( -o <FILE> | --output <FILE> ) | ( -O [<DIRECTORY>] | --output-auto-name [<DIRECTORY>] ) | ( --sign | --sign-as <KEYID> | --sign-ssl <IDFILE> | --dont-sign ) | --dry-run | --xml-output | ( ( -s | --summary ) | --no-summary ) | ( --edit-description | --dont-edit-description ) | ( --set-default | --no-set-default ) | --repodir <DIRECTORY> | --sendmail-command <COMMAND> | --ignore-unrelated-repos | --logfile <FILE> | --delete-logfile | --remote-repo <URL> | --context <FILENAME> | ( --ssh-cm | --no-ssh-cm ) | ( --http-pipelining | --no-http-pipelining ) | --no-cache | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... [REPOSITORY];
darcs apply ( ( --verify <PUBRING> | --verify-ssl <KEYS> | --no-verify ) | ( ( -a | --all ) | ( -i | --interactive ) ) | --dry-run | --xml-output | ( --mark-conflicts | --allow-conflicts | --no-resolve-conflicts | --dont-allow-conflicts | --skip-conflicts ) | --external-merge <COMMAND> | ( --no-test | --test ) | ( --leave-test-directory | --remove-test-directory ) | --repodir <DIRECTORY> | --reply <FROM> | --cc <EMAIL> | --happy-forwarding | --sendmail-command <COMMAND> | --ignore-times | ( --compress | --dont-compress ) | ( --set-scripts-executable | --dont-set-scripts-executable ) | --umask <UMASK> | ( --restrict-paths | --dont-restrict-paths ) | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... <PATCHFILE>;
darcs get ( ( --repo-name <DIRECTORY> | --repodir <DIRECTORY> ) | ( --partial | --lazy | --ephemeral | --complete ) | ( --to-match <PATTERN> | --to-patch <REGEXP> | ( -t <REGEXP> | --tag <REGEXP> ) | --context <FILENAME> ) | ( --set-default | --no-set-default ) | ( --set-scripts-executable | --dont-set-scripts-executable ) | --nolinks | ( --hashed | --old-fashioned-inventory ) | ( --ssh-cm | --no-ssh-cm ) | ( --http-pipelining | --no-http-pipelining ) | --no-cache | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... <REPOSITORY> [<DIRECTORY>];
darcs put ( ( --to-match <PATTERN> | --to-patch <REGEXP> | ( -t <REGEXP> | --tag <REGEXP> ) | --context <FILENAME> ) | ( --set-scripts-executable | --dont-set-scripts-executable ) | ( --hashed | --old-fashioned-inventory ) | ( --set-default | --no-set-default ) | --repodir <DIRECTORY> | ( --apply-as <USERNAME> | --apply-as-myself ) | ( --ssh-cm | --no-ssh-cm ) | ( --http-pipelining | --no-http-pipelining ) | --no-cache | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... <NEW_REPOSITORY>;
darcs initialize ( ( --hashed | --darcs-2 | --old-fashioned-inventory ) | --repodir <DIRECTORY> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... ;
darcs optimize ( --repodir <DIRECTORY> | --reorder-patches | --sibling <URL> | --relink | --relink-pristine | --upgrade | --pristine | ( --compress | --dont-compress | --uncompress ) | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... ;
darcs check ( ( --complete | --partial ) | ( --no-test | --test ) | ( --leave-test-directory | --remove-test-directory ) | --repodir <DIRECTORY> | --ignore-times | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... ;
darcs repair ( --repodir <DIRECTORY> | --umask <UMASK> | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... ;
darcs convert ( ( --repo-name <DIRECTORY> | --repodir <DIRECTORY> ) | ( --set-scripts-executable | --dont-set-scripts-executable ) | ( --ssh-cm | --no-ssh-cm ) | ( --http-pipelining | --no-http-pipelining ) | --no-cache | ( --debug | --debug-verbose | --debug-http | ( -v | --verbose ) | ( -q | --quiet ) | --standard-verbosity ) | --timings | ( --posthook <COMMAND> | --no-posthook ) | ( --prompt-posthook | --run-posthook ) | ( --prehook <COMMAND> | --no-prehook ) | ( --prompt-prehook | --run-prehook ) ) ... <SOURCE> [<DESTINATION>]
07070100000010000081A40000000000000000000000016248715500000081000000000000000000000000000000000000003600000000compleat-1.0+git.20220402.ec8fccc/examples/htop.usagehtop [--delay=<DELAY> | --no-colour | --pid=<PID> ... | --sort-key=<COLUMN> | --user=<USERNAME> ] ...;
htop (--help | --version)
07070100000011000081A4000000000000000000000001624871550000005A000000000000000000000000000000000000003500000000compleat-1.0+git.20220402.ec8fccc/examples/top.usagetop [-b | -c | -H | -i | -s | -S | -d <delay> | -n <num> | -p <pid> ...] ...;
top (-h|-v)
07070100000012000081A40000000000000000000000016248715500000884000000000000000000000000000000000000002D00000000compleat-1.0+git.20220402.ec8fccc/stack.yaml# This file was automatically generated by 'stack init'
#
# Some commonly used options have been documented as comments in this file.
# For advanced use and comprehensive documentation of the format, please see:
# https://docs.haskellstack.org/en/stable/yaml_configuration/

# Resolver to choose a 'specific' stackage snapshot or a compiler version.
# A snapshot resolver dictates the compiler version and the set of packages
# to be used for project dependencies. For example:
#
# resolver: lts-3.5
# resolver: nightly-2015-09-21
# resolver: ghc-7.10.2
# resolver: ghcjs-0.1.0_ghc-7.10.2
# resolver:
#  name: custom-snapshot
#  location: "./custom-snapshot.yaml"
resolver: lts-13.23

# User packages to be built.
# Various formats can be used as shown in the example below.
#
# packages:
# - some-directory
# - https://example.com/foo/bar/baz-0.0.2.tar.gz
# - location:
#    git: https://github.com/commercialhaskell/stack.git
#    commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a
# - location: https://github.com/commercialhaskell/stack/commit/e7b331f14bcffb8367cd58fbfc8b40ec7642100a
#   extra-dep: true
#  subdirs:
#  - auto-update
#  - wai
#
# A package marked 'extra-dep: true' will only be built if demanded by a
# non-dependency (i.e. a user package), and its test suites and benchmarks
# will not be run. This is useful for tweaking upstream packages.
packages:
- .
# Dependency packages to be pulled from upstream that are not in the resolver
# (e.g., acme-missiles-0.3)
# extra-deps: []

# Override default flag values for local packages and extra-deps
# flags: {}

# Extra package databases containing global packages
# extra-package-dbs: []

# Control whether we use the GHC we find on the path
# system-ghc: true
#
# Require a specific version of stack, using version ranges
# require-stack-version: -any # Default
# require-stack-version: ">=1.6"
#
# Override the architecture used by stack, especially useful on Windows
# arch: i386
# arch: x86_64
#
# Extra directories used by stack for building
# extra-include-dirs: [/path/to/dir]
# extra-lib-dirs: [/path/to/dir]
#
# Allow a newer minor version of GHC than the snapshot specifies
# compiler-check: newer-minor
07070100000000000000000000000000000000000000010000000000000000000000000000000000000000000000000000000B00000000TRAILER!!!92 blocks
openSUSE Build Service is sponsored by