convert all commands to work with optparse-applicative

Still no options though.
This commit is contained in:
Joey Hess 2015-07-08 15:08:02 -04:00
parent 3125da54f6
commit 6e5c1f8db3
99 changed files with 391 additions and 297 deletions

View file

@ -20,7 +20,7 @@ type Batchable t = BatchMode -> t -> CommandStart
-- In batch mode, one line at a time is read, parsed, and a reply output to -- In batch mode, one line at a time is read, parsed, and a reply output to
-- stdout. In non batch mode, the command's parameters are parsed and -- stdout. In non batch mode, the command's parameters are parsed and
-- a reply output for each. -- a reply output for each.
batchable :: ((t -> CommandStart) -> CommandSeek) -> Batchable t -> CommandSeek batchable :: ((t -> CommandStart) -> CmdParams -> CommandSeek) -> Batchable t -> CmdParams -> CommandSeek
batchable seeker starter params = ifM (getOptionFlag batchOption) batchable seeker starter params = ifM (getOptionFlag batchOption)
( batchloop ( batchloop
, seeker (starter NoBatch) params , seeker (starter NoBatch) params

View file

@ -16,7 +16,6 @@ import Utility.Env
import Annex.Ssh import Annex.Ssh
import qualified Command.Add import qualified Command.Add
{-
import qualified Command.Unannex import qualified Command.Unannex
import qualified Command.Drop import qualified Command.Drop
import qualified Command.Move import qualified Command.Move
@ -117,12 +116,10 @@ import qualified Command.TestRemote
#ifdef WITH_EKG #ifdef WITH_EKG
import System.Remote.Monitoring import System.Remote.Monitoring
#endif #endif
-}
cmds :: [Command] cmds :: [Command]
cmds = cmds =
[ Command.Add.cmd [ Command.Add.cmd
{-
, Command.Get.cmd , Command.Get.cmd
, Command.Drop.cmd , Command.Drop.cmd
, Command.Move.cmd , Command.Move.cmd
@ -221,7 +218,6 @@ cmds =
, Command.FuzzTest.cmd , Command.FuzzTest.cmd
, Command.TestRemote.cmd , Command.TestRemote.cmd
#endif #endif
-}
] ]
header :: String header :: String

View file

@ -1,6 +1,6 @@
{- git-annex usage messages {- git-annex usage messages
- -
- Copyright 2010-2011 Joey Hess <id@joeyh.name> - Copyright 2010-2015 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
@ -8,10 +8,10 @@
module CmdLine.Usage where module CmdLine.Usage where
import Common.Annex import Common.Annex
import Types.Command import Types.Command
import System.Console.GetOpt import System.Console.GetOpt
import qualified Options.Applicative as O
usageMessage :: String -> String usageMessage :: String -> String
usageMessage s = "Usage: " ++ s usageMessage s = "Usage: " ++ s
@ -56,6 +56,13 @@ commandUsage cmd = unlines
, "[option ...]" , "[option ...]"
] ]
{- Simple CommandParser generator, for when the CommandSeek wants all
- non-option parameters. -}
withParams :: (CmdParams -> CommandSeek) -> String -> CommandParser
withParams mkseek paramdesc = mkseek <$> O.many cmdparams
where
cmdparams = O.argument O.str (O.metavar paramdesc)
{- Descriptions of params used in usage messages. -} {- Descriptions of params used in usage messages. -}
paramPaths :: String paramPaths :: String
paramPaths = paramRepeating paramPath -- most often used paramPaths = paramRepeating paramPath -- most often used

View file

@ -7,7 +7,6 @@
module Command ( module Command (
command, command,
commandParser,
noRepo, noRepo,
noCommit, noCommit,
noMessages, noMessages,
@ -33,20 +32,11 @@ import CmdLine.Action as ReExported
import CmdLine.Option as ReExported import CmdLine.Option as ReExported
import CmdLine.GitAnnex.Options as ReExported import CmdLine.GitAnnex.Options as ReExported
import qualified Options.Applicative as O
{- Generates a normal Command -} {- Generates a normal Command -}
command :: String -> String -> CommandSection -> String -> (Command -> CommandParser) -> Command command :: String -> CommandSection -> String -> String -> (String -> CommandParser) -> Command
command name paramdesc section desc parser = c command name section desc paramdesc mkparser =
where Command [] Nothing commonChecks False False name paramdesc
c = Command [] Nothing commonChecks False False name paramdesc section desc (parser c) section desc (mkparser paramdesc)
{- Simple CommandParser generator, for when the CommandSeek wants all
- non-option parameters. -}
commandParser :: (CmdParams -> CommandSeek) -> Command -> CommandParser
commandParser mkseek c = mkseek <$> O.many cmdparams
where
cmdparams = O.argument O.str (O.metavar (cmdparamdesc c))
{- Indicates that a command doesn't need to commit any changes to {- Indicates that a command doesn't need to commit any changes to
- the git-annex branch. -} - the git-annex branch. -}

View file

@ -36,8 +36,8 @@ import Control.Exception (IOException)
cmd :: Command cmd :: Command
cmd = notBareRepo $ withOptions addOptions $ cmd = notBareRepo $ withOptions addOptions $
command "add" paramPaths SectionCommon "add files to annex" command "add" SectionCommon "add files to annex"
(commandParser seek) paramPaths (withParams seek)
addOptions :: [Option] addOptions :: [Option]
addOptions = includeDotFilesOption : fileMatchingOptions addOptions = includeDotFilesOption : fileMatchingOptions
@ -71,8 +71,8 @@ startSmall file = do
performAdd :: FilePath -> CommandPerform performAdd :: FilePath -> CommandPerform
performAdd file = do performAdd file = do
params <- forceParams ps <- forceParams
Annex.Queue.addCommand "add" (params++[Param "--"]) [file] Annex.Queue.addCommand "add" (ps++[Param "--"]) [file]
next $ return True next $ return True
{- The add subcommand annexes a file, generating a key for it using a {- The add subcommand annexes a file, generating a key for it using a
@ -279,8 +279,8 @@ addLink :: FilePath -> Key -> Maybe InodeCache -> Annex ()
addLink file key mcache = ifM (coreSymlinks <$> Annex.getGitConfig) addLink file key mcache = ifM (coreSymlinks <$> Annex.getGitConfig)
( do ( do
_ <- link file key mcache _ <- link file key mcache
params <- forceParams ps <- forceParams
Annex.Queue.addCommand "add" (params++[Param "--"]) [file] Annex.Queue.addCommand "add" (ps++[Param "--"]) [file]
, do , do
l <- link file key mcache l <- link file key mcache
addAnnexLink l file addAnnexLink l file

View file

@ -15,10 +15,12 @@ import Command.Unused (withUnusedMaps, UnusedMaps(..), startUnused)
import Types.Key import Types.Key
cmd :: Command cmd :: Command
cmd = notDirect $ command "addunused" (paramRepeating paramNumRange) cmd = notDirect $
seek SectionMaintenance "add back unused files" command "addunused" SectionMaintenance
"add back unused files"
(paramRepeating paramNumRange) (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withUnusedMaps start seek = withUnusedMaps start
start :: UnusedMaps -> Int -> CommandStart start :: UnusedMaps -> Int -> CommandStart

View file

@ -39,8 +39,8 @@ import qualified Utility.Quvi as Quvi
cmd :: Command cmd :: Command
cmd = notBareRepo $ withOptions [fileOption, pathdepthOption, relaxedOption, rawOption] $ cmd = notBareRepo $ withOptions [fileOption, pathdepthOption, relaxedOption, rawOption] $
command "addurl" (paramRepeating paramUrl) seek command "addurl" SectionCommon "add urls to annex"
SectionCommon "add urls to annex" (paramRepeating paramUrl) (withParams seek)
fileOption :: Option fileOption :: Option
fileOption = fieldOption [] "file" paramFile "specify what file the url is added to" fileOption = fieldOption [] "file" paramFile "specify what file the url is added to"
@ -54,7 +54,7 @@ relaxedOption = flagOption [] "relaxed" "skip size check"
rawOption :: Option rawOption :: Option
rawOption = flagOption [] "raw" "disable special handling for torrents, quvi, etc" rawOption = flagOption [] "raw" "disable special handling for torrents, quvi, etc"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek us = do seek us = do
optfile <- getOptionField fileOption return optfile <- getOptionField fileOption return
relaxed <- getOptionFlag relaxedOption relaxed <- getOptionFlag relaxedOption

View file

@ -21,8 +21,9 @@ import System.Environment
cmd :: Command cmd :: Command
cmd = noRepo checkNoRepoOpts $ dontCheck repoExists $ withOptions options $ cmd = noRepo checkNoRepoOpts $ dontCheck repoExists $ withOptions options $
notBareRepo $ command "assistant" paramNothing seek SectionCommon notBareRepo $ command "assistant" SectionCommon
"automatically sync changes" "automatically sync changes"
paramNothing (withParams seek)
options :: [Option] options :: [Option]
options = options =
@ -42,7 +43,7 @@ autoStopOption = flagOption [] "autostop" "stop in known repositories"
startDelayOption :: Option startDelayOption :: Option
startDelayOption = fieldOption [] "startdelay" paramNumber "delay before running startup scan" startDelayOption = fieldOption [] "startdelay" paramNumber "delay before running startup scan"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
stopdaemon <- getOptionFlag Command.Watch.stopOption stopdaemon <- getOptionFlag Command.Watch.stopOption
foreground <- getOptionFlag Command.Watch.foregroundOption foreground <- getOptionFlag Command.Watch.foregroundOption

View file

@ -15,10 +15,13 @@ import Annex
import Types.Messages import Types.Messages
cmd :: Command cmd :: Command
cmd = noCommit $ command "checkpresentkey" (paramPair paramKey paramRemote) seek cmd = noCommit $
SectionPlumbing "check if key is present in remote" command "checkpresentkey" SectionPlumbing
"check if key is present in remote"
(paramPair paramKey paramRemote)
(withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -13,9 +13,9 @@ import qualified Annex.Branch
import qualified Git import qualified Git
cmd :: Command cmd :: Command
cmd = command "commit" paramNothing cmd = command "commit" SectionPlumbing
SectionPlumbing "commits any staged changes to the git-annex branch" "commits any staged changes to the git-annex branch"
(commandParser seek) paramNothing (withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -16,9 +16,10 @@ import qualified Git.Config
import Remote.GCrypt (coreGCryptId) import Remote.GCrypt (coreGCryptId)
cmd :: Command cmd :: Command
cmd = noCommit $ command "configlist" paramNothing cmd = noCommit $
SectionPlumbing "outputs relevant git configuration" command "configlist" SectionPlumbing
(commandParser seek) "outputs relevant git configuration"
paramNothing (withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -14,10 +14,11 @@ import Annex.Content
cmd :: Command cmd :: Command
cmd = withOptions [batchOption] $ noCommit $ noMessages $ cmd = withOptions [batchOption] $ noCommit $ noMessages $
command "contentlocation" (paramRepeating paramKey) seek command "contentlocation" SectionPlumbing
SectionPlumbing "looks up content for a key" "looks up content for a key"
(paramRepeating paramKey) (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = batchable withKeys start seek = batchable withKeys start
start :: Batchable Key start :: Batchable Key

View file

@ -15,13 +15,15 @@ import Annex.Wanted
import Annex.NumCopies import Annex.NumCopies
cmd :: Command cmd :: Command
cmd = withOptions copyOptions $ command "copy" paramPaths seek cmd = withOptions copyOptions $
SectionCommon "copy content of files to/from another repository" command "copy" SectionCommon
"copy content of files to/from another repository"
paramPaths (withParams seek)
copyOptions :: [Option] copyOptions :: [Option]
copyOptions = Command.Move.moveOptions ++ [autoOption] copyOptions = Command.Move.moveOptions ++ [autoOption]
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
to <- getOptionField toOption Remote.byNameWithUUID to <- getOptionField toOption Remote.byNameWithUUID
from <- getOptionField fromOption Remote.byNameWithUUID from <- getOptionField fromOption Remote.byNameWithUUID

View file

@ -18,14 +18,14 @@ import Remote (keyLocations)
cmd :: Command cmd :: Command
cmd = withOptions [keyOption] $ cmd = withOptions [keyOption] $
command "dead" (paramRepeating paramRemote) seek command "dead" SectionSetup "hide a lost repository or key"
SectionSetup "hide a lost repository or key" (paramRepeating paramRemote) (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = maybe (trustCommand "dead" DeadTrusted ps) (flip seekKey ps) seek ps = maybe (trustCommand "dead" DeadTrusted ps) (flip seekKey ps)
=<< Annex.getField "key" =<< Annex.getField "key"
seekKey :: String -> CommandSeek seekKey :: String -> CmdParams -> CommandSeek
seekKey ks = case file2key ks of seekKey ks = case file2key ks of
Nothing -> error "Invalid key" Nothing -> error "Invalid key"
Just key -> withNothing (startKey key) Just key -> withNothing (startKey key)

View file

@ -13,10 +13,12 @@ import qualified Remote
import Logs.UUID import Logs.UUID
cmd :: Command cmd :: Command
cmd = command "describe" (paramPair paramRemote paramDesc) seek cmd = command "describe" SectionSetup
SectionSetup "change description of a repository" "change description of a repository"
(paramPair paramRemote paramDesc)
(withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -15,10 +15,11 @@ import Git.Types
cmd :: Command cmd :: Command
cmd = dontCheck repoExists $ cmd = dontCheck repoExists $
command "diffdriver" ("[-- cmd --]") seek command "diffdriver" SectionPlumbing
SectionPlumbing "external git diff driver shim" "external git diff driver shim"
("-- cmd --") (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -17,10 +17,10 @@ import Annex.Direct
cmd :: Command cmd :: Command
cmd = notBareRepo $ noDaemonRunning $ cmd = notBareRepo $ noDaemonRunning $
command "direct" paramNothing seek command "direct" SectionSetup "switch repository to direct mode"
SectionSetup "switch repository to direct mode" paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
start :: CommandStart start :: CommandStart

View file

@ -23,8 +23,10 @@ import Annex.Notification
import qualified Data.Set as S import qualified Data.Set as S
cmd :: Command cmd :: Command
cmd = withOptions (dropOptions) $ command "drop" paramPaths seek cmd = withOptions (dropOptions) $
SectionCommon "indicate content of files not currently wanted" command "drop" SectionCommon
"indicate content of files not currently wanted"
paramPaths (withParams seek)
dropOptions :: [Option] dropOptions :: [Option]
dropOptions = dropFromOption : annexedMatchingOptions ++ [autoOption] ++ keyOptions dropOptions = dropFromOption : annexedMatchingOptions ++ [autoOption] ++ keyOptions
@ -32,7 +34,7 @@ dropOptions = dropFromOption : annexedMatchingOptions ++ [autoOption] ++ keyOpti
dropFromOption :: Option dropFromOption :: Option
dropFromOption = fieldOption ['f'] "from" paramRemote "drop content from a remote" dropFromOption = fieldOption ['f'] "from" paramRemote "drop content from a remote"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
from <- getOptionField dropFromOption Remote.byNameWithUUID from <- getOptionField dropFromOption Remote.byNameWithUUID
auto <- getOptionFlag autoOption auto <- getOptionFlag autoOption

View file

@ -14,9 +14,11 @@ import Logs.Location
import Annex.Content import Annex.Content
cmd :: Command cmd :: Command
cmd = noCommit $ command "dropkey" (paramRepeating paramKey) cmd = noCommit $
SectionPlumbing "drops annexed content for specified keys" command "dropkey" SectionPlumbing
(commandParser seek) "drops annexed content for specified keys"
(paramRepeating paramKey)
(withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek = withKeys start seek = withKeys start

View file

@ -18,10 +18,11 @@ import Annex.NumCopies
cmd :: Command cmd :: Command
cmd = withOptions [Command.Drop.dropFromOption] $ cmd = withOptions [Command.Drop.dropFromOption] $
command "dropunused" (paramRepeating paramNumRange) command "dropunused" SectionMaintenance
seek SectionMaintenance "drop unused file content" "drop unused file content"
(paramRepeating paramNumRange) (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
numcopies <- getNumCopies numcopies <- getNumCopies
withUnusedMaps (start numcopies) ps withUnusedMaps (start numcopies) ps

View file

@ -16,11 +16,12 @@ import qualified Command.InitRemote as InitRemote
import qualified Data.Map as M import qualified Data.Map as M
cmd :: Command cmd :: Command
cmd = command "enableremote" cmd = command "enableremote" SectionSetup
"enables use of an existing special remote"
(paramPair paramName $ paramOptional $ paramRepeating paramKeyValue) (paramPair paramName $ paramOptional $ paramRepeating paramKeyValue)
seek SectionSetup "enables use of an existing special remote" (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -16,10 +16,11 @@ import Types.Key
cmd :: Command cmd :: Command
cmd = noCommit $ noMessages $ withOptions [formatOption, jsonOption, batchOption] $ cmd = noCommit $ noMessages $ withOptions [formatOption, jsonOption, batchOption] $
command "examinekey" (paramRepeating paramKey) seek command "examinekey" SectionPlumbing
SectionPlumbing "prints information from a key" "prints information from a key"
(paramRepeating paramKey) (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
format <- getFormat format <- getFormat
batchable withKeys (start format) ps batchable withKeys (start format) ps

View file

@ -21,8 +21,10 @@ import Data.Time.Clock.POSIX
import qualified Data.Map as M import qualified Data.Map as M
cmd :: Command cmd :: Command
cmd = withOptions [activityOption, noActOption] $ command "expire" paramExpire seek cmd = withOptions [activityOption, noActOption] $
SectionMaintenance "expire inactive repositories" command "expire" SectionMaintenance
"expire inactive repositories"
paramExpire (withParams seek)
paramExpire :: String paramExpire :: String
paramExpire = (paramRepeating $ paramOptional paramRemote ++ ":" ++ paramTime) paramExpire = (paramRepeating $ paramOptional paramRemote ++ ":" ++ paramTime)
@ -33,7 +35,7 @@ activityOption = fieldOption [] "activity" "Name" "specify activity"
noActOption :: Option noActOption :: Option
noActOption = flagOption [] "no-act" "don't really do anything" noActOption = flagOption [] "no-act" "don't really do anything"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
expire <- parseExpire ps expire <- parseExpire ps
wantact <- getOptionField activityOption (pure . parseActivity) wantact <- getOptionField activityOption (pure . parseActivity)

View file

@ -21,7 +21,8 @@ import Types.Key
cmd :: Command cmd :: Command
cmd = withOptions annexedMatchingOptions $ mkCommand $ cmd = withOptions annexedMatchingOptions $ mkCommand $
command "find" paramPaths seek SectionQuery "lists available files" command "find" SectionQuery "lists available files"
paramPaths (withParams seek)
mkCommand :: Command -> Command mkCommand :: Command -> Command
mkCommand = noCommit . noMessages . withOptions [formatOption, print0Option, jsonOption] mkCommand = noCommit . noMessages . withOptions [formatOption, print0Option, jsonOption]
@ -38,7 +39,7 @@ print0Option = Option [] ["print0"] (NoArg set)
where where
set = Annex.setField (optionName formatOption) "${file}\0" set = Annex.setField (optionName formatOption) "${file}\0"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
format <- getFormat format <- getFormat
withFilesInGit (whenAnnexed $ start format) ps withFilesInGit (whenAnnexed $ start format) ps

View file

@ -12,10 +12,11 @@ import qualified Command.Find as Find
cmd :: Command cmd :: Command
cmd = withOptions nonWorkTreeMatchingOptions $ Find.mkCommand $ cmd = withOptions nonWorkTreeMatchingOptions $ Find.mkCommand $
command "findref" paramRef seek SectionPlumbing command "findref" SectionPlumbing
"lists files in a git ref" "lists files in a git ref"
paramRef (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek refs = do seek refs = do
format <- Find.getFormat format <- Find.getFormat
Find.start format `withFilesInRefs` refs Find.start format `withFilesInRefs` refs

View file

@ -20,9 +20,9 @@ import Utility.Touch
cmd :: Command cmd :: Command
cmd = notDirect $ noCommit $ withOptions annexedMatchingOptions $ cmd = notDirect $ noCommit $ withOptions annexedMatchingOptions $
command "fix" paramPaths command "fix" SectionMaintenance
SectionMaintenance "fix up symlinks to point to annexed content" "fix up symlinks to point to annexed content"
(commandParser seek) paramPaths (withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek = withFilesInGit $ whenAnnexed start seek = withFilesInGit $ whenAnnexed start

View file

@ -16,8 +16,10 @@ import qualified Annex
import Data.Time.Clock.POSIX import Data.Time.Clock.POSIX
cmd :: Command cmd :: Command
cmd = withOptions forgetOptions $ command "forget" paramNothing seek cmd = withOptions forgetOptions $
SectionMaintenance "prune git-annex branch history" command "forget" SectionMaintenance
"prune git-annex branch history"
paramNothing (withParams seek)
forgetOptions :: [Option] forgetOptions :: [Option]
forgetOptions = [dropDeadOption] forgetOptions = [dropDeadOption]
@ -25,7 +27,7 @@ forgetOptions = [dropDeadOption]
dropDeadOption :: Option dropDeadOption :: Option
dropDeadOption = flagOption [] "drop-dead" "drop references to dead repositories" dropDeadOption = flagOption [] "drop-dead" "drop references to dead repositories"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
dropdead <- getOptionFlag dropDeadOption dropdead <- getOptionFlag dropDeadOption
withNothing (start dropdead) ps withNothing (start dropdead) ps

View file

@ -21,10 +21,11 @@ import Network.URI
cmd :: Command cmd :: Command
cmd = notDirect $ notBareRepo $ cmd = notDirect $ notBareRepo $
command "fromkey" (paramPair paramKey paramPath) seek command "fromkey" SectionPlumbing "adds a file using a specific key"
SectionPlumbing "adds a file using a specific key" (paramPair paramKey paramPath)
(withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
force <- Annex.getState Annex.force force <- Annex.getState Annex.force
withWords (start force) ps withWords (start force) ps

View file

@ -41,8 +41,9 @@ import Data.Time.Clock.POSIX
import System.Posix.Types (EpochTime) import System.Posix.Types (EpochTime)
cmd :: Command cmd :: Command
cmd = withOptions fsckOptions $ command "fsck" paramPaths seek cmd = withOptions fsckOptions $
SectionMaintenance "check for problems" command "fsck" SectionMaintenance "check for problems"
paramPaths (withParams seek)
fsckFromOption :: Option fsckFromOption :: Option
fsckFromOption = fieldOption ['f'] "from" paramRemote "check remote" fsckFromOption = fieldOption ['f'] "from" paramRemote "check remote"
@ -65,7 +66,7 @@ fsckOptions =
, incrementalScheduleOption , incrementalScheduleOption
] ++ keyOptions ++ annexedMatchingOptions ] ++ keyOptions ++ annexedMatchingOptions
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
from <- getOptionField fsckFromOption Remote.byNameWithUUID from <- getOptionField fsckFromOption Remote.byNameWithUUID
u <- maybe getUUID (pure . Remote.uuid) from u <- maybe getUUID (pure . Remote.uuid) from

View file

@ -21,10 +21,12 @@ import Test.QuickCheck
import Control.Concurrent import Control.Concurrent
cmd :: Command cmd :: Command
cmd = notBareRepo $ command "fuzztest" paramNothing seek SectionTesting cmd = notBareRepo $
command "fuzztest" SectionTesting
"generates fuzz test files" "generates fuzz test files"
paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
start :: CommandStart start :: CommandStart

View file

@ -15,9 +15,9 @@ import qualified Git
cmd :: Command cmd :: Command
cmd = dontCheck repoExists $ noCommit $ cmd = dontCheck repoExists $ noCommit $
command "gcryptsetup" paramValue command "gcryptsetup" SectionPlumbing
SectionPlumbing "sets up gcrypt repository" "sets up gcrypt repository"
(commandParser seek) paramValue (withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek = withStrings start seek = withStrings start

View file

@ -17,14 +17,16 @@ import Annex.Wanted
import qualified Command.Move import qualified Command.Move
cmd :: Command cmd :: Command
cmd = withOptions getOptions $ command "get" paramPaths seek cmd = withOptions getOptions $
SectionCommon "make content of annexed files available" command "get" SectionCommon
"make content of annexed files available"
paramPaths (withParams seek)
getOptions :: [Option] getOptions :: [Option]
getOptions = fromOption : autoOption : jobsOption : annexedMatchingOptions getOptions = fromOption : autoOption : jobsOption : annexedMatchingOptions
++ incompleteOption : keyOptions ++ incompleteOption : keyOptions
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
from <- getOptionField fromOption Remote.byNameWithUUID from <- getOptionField fromOption Remote.byNameWithUUID
auto <- getOptionFlag autoOption auto <- getOptionFlag autoOption

View file

@ -16,10 +16,10 @@ import Types.Group
import qualified Data.Set as S import qualified Data.Set as S
cmd :: Command cmd :: Command
cmd = command "group" (paramPair paramRemote paramDesc) seek cmd = command "group" SectionSetup "add a repository to a group"
SectionSetup "add a repository to a group" (paramPair paramRemote paramDesc) (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -13,10 +13,12 @@ import Logs.PreferredContent
import Command.Wanted (performGet, performSet) import Command.Wanted (performGet, performSet)
cmd :: Command cmd :: Command
cmd = command "groupwanted" (paramPair paramGroup (paramOptional paramExpression)) seek cmd = command "groupwanted" SectionSetup
SectionSetup "get or set groupwanted expression" "get or set groupwanted expression"
(paramPair paramGroup (paramOptional paramExpression))
(withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -23,9 +23,10 @@ import System.Console.GetOpt
cmd :: Command cmd :: Command
cmd = noCommit $ noRepo startNoRepo $ dontCheck repoExists $ cmd = noCommit $ noRepo startNoRepo $ dontCheck repoExists $
command "help" "COMMAND" seek SectionCommon "display help" command "help" SectionCommon "display help"
"COMMAND" (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart
@ -47,7 +48,7 @@ showCommonOptions = putStrLn $ usageInfo "Common options:" gitAnnexOptions
showGeneralHelp :: IO () showGeneralHelp :: IO ()
showGeneralHelp = putStrLn $ unlines showGeneralHelp = putStrLn $ unlines
[ "The most frequently used git-annex commands are:" [ "The most frequently used git-annex commands are:"
, unlines $ map cmdline $ concat , unlines $ map cmdline $
[ Command.Init.cmd [ Command.Init.cmd
, Command.Add.cmd , Command.Add.cmd
, Command.Drop.cmd , Command.Drop.cmd

View file

@ -23,8 +23,10 @@ import Types.TrustLevel
import Logs.Trust import Logs.Trust
cmd :: Command cmd :: Command
cmd = withOptions opts $ notBareRepo $ command "import" paramPaths seek cmd = withOptions opts $ notBareRepo $
SectionCommon "move and add files from outside git working copy" command "import" SectionCommon
"move and add files from outside git working copy"
paramPaths (withParams seek)
opts :: [Option] opts :: [Option]
opts = duplicateModeOptions ++ fileMatchingOptions opts = duplicateModeOptions ++ fileMatchingOptions
@ -60,7 +62,7 @@ getDuplicateMode = go . catMaybes <$> mapM getflag [minBound..maxBound]
go ms = error $ "cannot combine " ++ go ms = error $ "cannot combine " ++
unwords (map (optionParam . fromJust . associatedOption) ms) unwords (map (optionParam . fromJust . associatedOption) ms)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
mode <- getDuplicateMode mode <- getDuplicateMode
repopath <- liftIO . absPath =<< fromRepo Git.repoPath repopath <- liftIO . absPath =<< fromRepo Git.repoPath

View file

@ -45,13 +45,13 @@ import Annex.MetaData
cmd :: Command cmd :: Command
cmd = notBareRepo $ withOptions [templateOption, relaxedOption, rawOption] $ cmd = notBareRepo $ withOptions [templateOption, relaxedOption, rawOption] $
command "importfeed" (paramRepeating paramUrl) seek command "importfeed" SectionCommon "import files from podcast feeds"
SectionCommon "import files from podcast feeds" (paramRepeating paramUrl) (withParams seek)
templateOption :: Option templateOption :: Option
templateOption = fieldOption [] "template" paramFormat "template for filenames" templateOption = fieldOption [] "template" paramFormat "template for filenames"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
tmpl <- getOptionField templateOption return tmpl <- getOptionField templateOption return
relaxed <- getOptionFlag relaxedOption relaxed <- getOptionFlag relaxedOption

View file

@ -12,9 +12,11 @@ import Command
import Annex.Content import Annex.Content
cmd :: Command cmd :: Command
cmd = noCommit $ command "inannex" (paramRepeating paramKey) cmd = noCommit $
SectionPlumbing "checks if keys are present in the annex" command "inannex" SectionPlumbing
(commandParser seek) "checks if keys are present in the annex"
(paramRepeating paramKey)
(withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek = withKeys start seek = withKeys start

View file

@ -24,10 +24,10 @@ import qualified Command.Add
cmd :: Command cmd :: Command
cmd = notBareRepo $ noDaemonRunning $ cmd = notBareRepo $ noDaemonRunning $
command "indirect" paramNothing seek command "indirect" SectionSetup "switch repository to indirect mode"
SectionSetup "switch repository to indirect mode" paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
start :: CommandStart start :: CommandStart

View file

@ -80,10 +80,11 @@ type StatState = StateT StatInfo Annex
cmd :: Command cmd :: Command
cmd = noCommit $ dontCheck repoExists $ withOptions (jsonOption : bytesOption : annexedMatchingOptions) $ cmd = noCommit $ dontCheck repoExists $ withOptions (jsonOption : bytesOption : annexedMatchingOptions) $
command "info" (paramRepeating paramItem) seek SectionQuery command "info" SectionQuery
"shows information about the specified item or the repository as a whole" "shows information about the specified item or the repository as a whole"
(paramRepeating paramItem) (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -13,9 +13,10 @@ import Annex.Init
cmd :: Command cmd :: Command
cmd = dontCheck repoExists $ cmd = dontCheck repoExists $
command "init" paramDesc seek SectionSetup "initialize git-annex" command "init" SectionSetup "initialize git-annex"
paramDesc (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -20,11 +20,12 @@ import Logs.Trust
import Data.Ord import Data.Ord
cmd :: Command cmd :: Command
cmd = command "initremote" cmd = command "initremote" SectionSetup
"creates a special (non-git) remote"
(paramPair paramName $ paramOptional $ paramRepeating paramKeyValue) (paramPair paramName $ paramOptional $ paramRepeating paramKeyValue)
seek SectionSetup "creates a special (non-git) remote" (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -25,13 +25,14 @@ import Git.Types (RemoteName)
cmd :: Command cmd :: Command
cmd = noCommit $ withOptions (allrepos : annexedMatchingOptions) $ cmd = noCommit $ withOptions (allrepos : annexedMatchingOptions) $
command "list" paramPaths seek command "list" SectionQuery
SectionQuery "show which remotes contain files" "show which remotes contain files"
paramPaths (withParams seek)
allrepos :: Option allrepos :: Option
allrepos = flagOption [] "allrepos" "show all repositories, not only remotes" allrepos = flagOption [] "allrepos" "show all repositories, not only remotes"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
list <- getList list <- getList
printHeader list printHeader list

View file

@ -14,10 +14,11 @@ import qualified Annex
cmd :: Command cmd :: Command
cmd = notDirect $ withOptions annexedMatchingOptions $ cmd = notDirect $ withOptions annexedMatchingOptions $
command "lock" paramPaths seek SectionCommon command "lock" SectionCommon
"undo unlock command" "undo unlock command"
paramPaths (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
withFilesUnlocked start ps withFilesUnlocked start ps
withFilesUnlockedToBeCommitted start ps withFilesUnlockedToBeCommitted start ps

View file

@ -40,7 +40,8 @@ type Outputter = Bool -> POSIXTime -> [UUID] -> Annex ()
cmd :: Command cmd :: Command
cmd = withOptions options $ cmd = withOptions options $
command "log" paramPaths seek SectionQuery "shows location log" command "log" SectionQuery "shows location log"
paramPaths (withParams seek)
options :: [Option] options :: [Option]
options = passthruOptions ++ [gourceOption] ++ annexedMatchingOptions options = passthruOptions ++ [gourceOption] ++ annexedMatchingOptions
@ -56,7 +57,7 @@ passthruOptions = map odate ["since", "after", "until", "before"] ++
gourceOption :: Option gourceOption :: Option
gourceOption = flagOption [] "gource" "format output for gource" gourceOption = flagOption [] "gource" "format output for gource"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
m <- Remote.uuidDescriptions m <- Remote.uuidDescriptions
zone <- liftIO getCurrentTimeZone zone <- liftIO getCurrentTimeZone

View file

@ -15,10 +15,11 @@ import Types.Key
cmd :: Command cmd :: Command
cmd = withOptions [batchOption] $ notBareRepo $ noCommit $ noMessages $ cmd = withOptions [batchOption] $ notBareRepo $ noCommit $ noMessages $
command "lookupkey" (paramRepeating paramFile) seek command "lookupkey" SectionPlumbing
SectionPlumbing "looks up key used for file" "looks up key used for file"
(paramRepeating paramFile) (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = batchable withStrings start seek = batchable withStrings start
start :: Batchable String start :: Batchable String

View file

@ -27,10 +27,11 @@ data Link = Link Git.Repo Git.Repo
cmd :: Command cmd :: Command
cmd = dontCheck repoExists $ cmd = dontCheck repoExists $
command "map" paramNothing seek SectionQuery command "map" SectionQuery
"generate map of repositories" "generate map of repositories"
paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
start :: CommandStart start :: CommandStart

View file

@ -14,10 +14,11 @@ import qualified Git.Branch
import Command.Sync (prepMerge, mergeLocal) import Command.Sync (prepMerge, mergeLocal)
cmd :: Command cmd :: Command
cmd = command "merge" paramNothing seek SectionMaintenance cmd = command "merge" SectionMaintenance
"automatically merge changes from remotes" "automatically merge changes from remotes"
paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
withNothing mergeBranch ps withNothing mergeBranch ps
withNothing mergeSynced ps withNothing mergeSynced ps

View file

@ -18,8 +18,9 @@ import Data.Time.Clock.POSIX
cmd :: Command cmd :: Command
cmd = withOptions metaDataOptions $ cmd = withOptions metaDataOptions $
command "metadata" paramPaths seek command "metadata"
SectionMetaData "sets or gets metadata of a file" SectionMetaData "sets or gets metadata of a file"
paramPaths (withParams seek)
metaDataOptions :: [Option] metaDataOptions :: [Option]
metaDataOptions = metaDataOptions =
@ -52,7 +53,7 @@ untagOption = Option ['u'] ["untag"] (ReqArg mkmod "TAG") "remove a tag"
where where
mkmod = storeModMeta . AddMeta tagMetaField . mkMetaValue (CurrentlySet False) mkmod = storeModMeta . AddMeta tagMetaField . mkMetaValue (CurrentlySet False)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
modmeta <- Annex.getState Annex.modmeta modmeta <- Annex.getState Annex.modmeta
getfield <- getOptionField getOption $ \ms -> getfield <- getOptionField getOption $ \ms ->

View file

@ -20,10 +20,11 @@ import qualified Annex
cmd :: Command cmd :: Command
cmd = notDirect $ withOptions annexedMatchingOptions $ cmd = notDirect $ withOptions annexedMatchingOptions $
command "migrate" paramPaths seek command "migrate" SectionUtility
SectionUtility "switch data to different backend" "switch data to different backend"
paramPaths (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withFilesInGit $ whenAnnexed start seek = withFilesInGit $ whenAnnexed start
start :: FilePath -> Key -> CommandStart start :: FilePath -> Key -> CommandStart

View file

@ -17,13 +17,15 @@ import Annex.Content
import Annex.NumCopies import Annex.NumCopies
cmd :: Command cmd :: Command
cmd = withOptions mirrorOptions $ command "mirror" paramPaths seek cmd = withOptions mirrorOptions $
SectionCommon "mirror content of files to/from another repository" command "mirror" SectionCommon
"mirror content of files to/from another repository"
paramPaths (withParams seek)
mirrorOptions :: [Option] mirrorOptions :: [Option]
mirrorOptions = fromToOptions ++ [jobsOption] ++ annexedMatchingOptions ++ keyOptions mirrorOptions = fromToOptions ++ [jobsOption] ++ annexedMatchingOptions ++ keyOptions
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
to <- getOptionField toOption Remote.byNameWithUUID to <- getOptionField toOption Remote.byNameWithUUID
from <- getOptionField fromOption Remote.byNameWithUUID from <- getOptionField fromOption Remote.byNameWithUUID

View file

@ -18,13 +18,15 @@ import Annex.Transfer
import Logs.Presence import Logs.Presence
cmd :: Command cmd :: Command
cmd = withOptions moveOptions $ command "move" paramPaths seek cmd = withOptions moveOptions $
SectionCommon "move content of files to/from another repository" command "move" SectionCommon
"move content of files to/from another repository"
paramPaths (withParams seek)
moveOptions :: [Option] moveOptions :: [Option]
moveOptions = fromToOptions ++ [jobsOption] ++ keyOptions ++ annexedMatchingOptions moveOptions = fromToOptions ++ [jobsOption] ++ keyOptions ++ annexedMatchingOptions
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
to <- getOptionField toOption Remote.byNameWithUUID to <- getOptionField toOption Remote.byNameWithUUID
from <- getOptionField fromOption Remote.byNameWithUUID from <- getOptionField fromOption Remote.byNameWithUUID

View file

@ -20,9 +20,10 @@ import Control.Concurrent.Async
import Control.Concurrent.STM import Control.Concurrent.STM
cmd :: Command cmd :: Command
cmd = noCommit $ command "notifychanges" paramNothing SectionPlumbing cmd = noCommit $
command "notifychanges" SectionPlumbing
"sends notification when git refs are changed" "sends notification when git refs are changed"
(commandParser seek) paramNothing (withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -14,10 +14,11 @@ import Annex.NumCopies
import Types.Messages import Types.Messages
cmd :: Command cmd :: Command
cmd = command "numcopies" paramNumber seek cmd = command "numcopies" SectionSetup
SectionSetup "configure desired number of copies" "configure desired number of copies"
paramNumber (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -29,9 +29,10 @@ import qualified Git.LsFiles as Git
import qualified Data.Set as S import qualified Data.Set as S
cmd :: Command cmd :: Command
cmd = command "pre-commit" paramPaths SectionPlumbing cmd = command "pre-commit" SectionPlumbing
"run by git pre-commit hook" "run by git pre-commit hook"
(commandParser seek) paramPaths
(withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek ps = lockPreCommitHook $ ifM isDirect seek ps = lockPreCommitHook $ ifM isDirect

View file

@ -19,10 +19,11 @@ import qualified Git.Branch
cmd :: Command cmd :: Command
cmd = notBareRepo $ cmd = notBareRepo $
command "proxy" ("-- git command") seek command "proxy" SectionPlumbing
SectionPlumbing "safely bypass direct mode guard" "safely bypass direct mode guard"
("-- git command") (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -19,11 +19,13 @@ import Utility.CopyFile
import qualified Remote import qualified Remote
cmd :: Command cmd :: Command
cmd = notDirect $ command "rekey" cmd = notDirect $
command "rekey" SectionPlumbing
"change keys used for files"
(paramRepeating $ paramPair paramPath paramKey) (paramRepeating $ paramPair paramPath paramKey)
seek SectionPlumbing "change keys used for files" (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withPairs start seek = withPairs start
start :: (FilePath, String) -> CommandStart start :: (FilePath, String) -> CommandStart

View file

@ -13,10 +13,13 @@ import Logs.Location
import Types.Key import Types.Key
cmd :: Command cmd :: Command
cmd = noCommit $ command "readpresentkey" (paramPair paramKey paramUUID) seek cmd = noCommit $
SectionPlumbing "read records of where key is present" command "readpresentkey" SectionPlumbing
"read records of where key is present"
(paramPair paramKey paramUUID)
(withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -21,9 +21,9 @@ import qualified Types.Backend
import qualified Backend import qualified Backend
cmd :: Command cmd :: Command
cmd = noCommit $ command "recvkey" paramKey cmd = noCommit $ command "recvkey" SectionPlumbing
SectionPlumbing "runs rsync in server mode to receive content" "runs rsync in server mode to receive content"
(commandParser seek) paramKey (withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek = withKeys start seek = withKeys start

View file

@ -17,10 +17,12 @@ import Command.FromKey (mkKey)
cmd :: Command cmd :: Command
cmd = notDirect $ notBareRepo $ cmd = notDirect $ notBareRepo $
command "registerurl" (paramPair paramKey paramUrl) seek command "registerurl"
SectionPlumbing "registers an url for a key" SectionPlumbing "registers an url for a key"
(paramPair paramKey paramUrl)
(withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -14,12 +14,14 @@ import Annex.UUID
import Types.UUID import Types.UUID
import qualified Remote import qualified Remote
cmd :: [Command] cmd :: Command
cmd = dontCheck repoExists $ cmd = dontCheck repoExists $
command "reinit" (paramUUID ++ "|" ++ paramDesc) seek command "reinit" SectionUtility
SectionUtility "initialize repository, reusing old UUID" "initialize repository, reusing old UUID"
(paramUUID ++ "|" ++ paramDesc)
(withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -14,11 +14,12 @@ import Annex.Content
import qualified Command.Fsck import qualified Command.Fsck
import qualified Backend import qualified Backend
cmd :: [Command] cmd :: Command
cmd = command "reinject" (paramPair "SRC" "DEST") seek cmd = command "reinject" SectionUtility
SectionUtility "sets content of annexed file" "sets content of annexed file"
(paramPair "SRC" "DEST") (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [FilePath] -> CommandStart start :: [FilePath] -> CommandStart

View file

@ -12,10 +12,12 @@ import Command
import RemoteDaemon.Core import RemoteDaemon.Core
cmd :: Command cmd :: Command
cmd = noCommit $ command "remotedaemon" paramNothing seek SectionPlumbing cmd = noCommit $
command "remotedaemon" SectionPlumbing
"detects when remotes have changed, and fetches from them" "detects when remotes have changed, and fetches from them"
paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
start :: CommandStart start :: CommandStart

View file

@ -18,9 +18,11 @@ import Annex.Version
cmd :: Command cmd :: Command
cmd = noCommit $ dontCheck repoExists $ cmd = noCommit $ dontCheck repoExists $
command "repair" paramNothing seek SectionMaintenance "recover broken git repository" command "repair" SectionMaintenance
"recover broken git repository"
paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
start :: CommandStart start :: CommandStart

View file

@ -15,10 +15,11 @@ import qualified Git.Branch
import Annex.AutoMerge import Annex.AutoMerge
cmd :: Command cmd :: Command
cmd = command "resolvemerge" paramNothing seek SectionPlumbing cmd = command "resolvemerge" SectionPlumbing
"resolve merge conflicts" "resolve merge conflicts"
paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
start :: CommandStart start :: CommandStart

View file

@ -15,10 +15,12 @@ import qualified Remote
cmd :: Command cmd :: Command
cmd = notBareRepo $ cmd = notBareRepo $
command "rmurl" (paramPair paramFile paramUrl) seek command "rmurl" SectionCommon
SectionCommon "record file is not available at url" "record file is not available at url"
(paramPair paramFile paramUrl)
(withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withPairs start seek = withPairs start
start :: (FilePath, String) -> CommandStart start :: (FilePath, String) -> CommandStart

View file

@ -18,10 +18,11 @@ import Types.Messages
import qualified Data.Set as S import qualified Data.Set as S
cmd :: Command cmd :: Command
cmd = command "schedule" (paramPair paramRemote (paramOptional paramExpression)) seek cmd = command "schedule" SectionSetup "get or set scheduled jobs"
SectionSetup "get or set scheduled jobs" (paramPair paramRemote (paramOptional paramExpression))
(withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -12,8 +12,9 @@ import Types.TrustLevel
import Command.Trust (trustCommand) import Command.Trust (trustCommand)
cmd :: Command cmd :: Command
cmd = command "semitrust" (paramRepeating paramRemote) seek cmd = command "semitrust" SectionSetup
SectionSetup "return repository to default trust level" "return repository to default trust level"
(paramRepeating paramRemote) (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = trustCommand "semitrust" SemiTrusted seek = trustCommand "semitrust" SemiTrusted

View file

@ -17,9 +17,10 @@ import qualified CmdLine.GitAnnexShell.Fields as Fields
import Utility.Metered import Utility.Metered
cmd :: Command cmd :: Command
cmd = noCommit $ command "sendkey" paramKey cmd = noCommit $
SectionPlumbing "runs rsync in server mode to send content" command "sendkey" SectionPlumbing
(commandParser seek) "runs rsync in server mode to send content"
paramKey (withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek = withKeys start seek = withKeys start

View file

@ -14,10 +14,11 @@ import Annex.Content
import Types.Key import Types.Key
cmd :: Command cmd :: Command
cmd = command "setkey" (paramPair paramKey paramPath) seek cmd = command "setkey" SectionPlumbing "sets annexed content for a key"
SectionPlumbing "sets annexed content for a key" (paramPair paramKey paramPath)
(withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -14,10 +14,13 @@ import Logs.Presence.Pure
import Types.Key import Types.Key
cmd :: Command cmd :: Command
cmd = noCommit $ command "setpresentkey" (paramPair paramKey (paramPair paramUUID "[1|0]")) seek cmd = noCommit $
SectionPlumbing "change records of where key is present" command "setpresentkey" SectionPlumbing
"change records of where key is present"
(paramPair paramKey (paramPair paramUUID "[1|0]"))
(withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -18,10 +18,11 @@ import qualified Git
cmd :: Command cmd :: Command
cmd = notBareRepo $ noCommit $ noMessages $ withOptions [jsonOption] $ cmd = notBareRepo $ noCommit $ noMessages $ withOptions [jsonOption] $
command "status" paramPaths seek SectionCommon command "status" SectionCommon
"show the working tree status" "show the working tree status"
paramPaths (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [FilePath] -> CommandStart start :: [FilePath] -> CommandStart

View file

@ -53,8 +53,9 @@ import qualified Data.Map as M
cmd :: Command cmd :: Command
cmd = withOptions syncOptions $ cmd = withOptions syncOptions $
command "sync" (paramRepeating paramRemote) command "sync" SectionCommon
seek SectionCommon "synchronize local repository with remotes" "synchronize local repository with remotes"
(paramRepeating paramRemote) (withParams seek)
syncOptions :: [Option] syncOptions :: [Option]
syncOptions = syncOptions =
@ -69,7 +70,7 @@ contentOption = flagOption [] "content" "also transfer file contents"
messageOption :: Option messageOption :: Option
messageOption = fieldOption ['m'] "message" "MSG" "specify commit message" messageOption = fieldOption ['m'] "message" "MSG" "specify commit message"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek rs = do seek rs = do
prepMerge prepMerge

View file

@ -13,10 +13,11 @@ import Messages
cmd :: Command cmd :: Command
cmd = noRepo startIO $ dontCheck repoExists $ cmd = noRepo startIO $ dontCheck repoExists $
command "test" paramNothing seek SectionTesting command "test" SectionTesting
"run built-in test suite" "run built-in test suite"
paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
{- We don't actually run the test suite here because of a dependency loop. {- We don't actually run the test suite here because of a dependency loop.

View file

@ -38,13 +38,14 @@ import qualified Data.Map as M
cmd :: Command cmd :: Command
cmd = withOptions [sizeOption] $ cmd = withOptions [sizeOption] $
command "testremote" paramRemote seek SectionTesting command "testremote" SectionTesting
"test transfers to/from a remote" "test transfers to/from a remote"
paramRemote (withParams seek)
sizeOption :: Option sizeOption :: Option
sizeOption = fieldOption [] "size" paramSize "base key size (default 1MiB)" sizeOption = fieldOption [] "size" paramSize "base key size (default 1MiB)"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
basesz <- fromInteger . fromMaybe (1024 * 1024) basesz <- fromInteger . fromMaybe (1024 * 1024)
<$> getOptionField sizeOption (pure . getsize) <$> getOptionField sizeOption (pure . getsize)

View file

@ -16,9 +16,10 @@ import qualified CmdLine.GitAnnexShell.Fields as Fields
import Utility.Metered import Utility.Metered
cmd :: Command cmd :: Command
cmd = noCommit $ command "transferinfo" paramKey SectionPlumbing cmd = noCommit $
command "transferinfo" SectionPlumbing
"updates sender on number of bytes of content received" "updates sender on number of bytes of content received"
(commandParser seek) paramKey (withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start

View file

@ -16,9 +16,10 @@ import qualified Remote
import Types.Remote import Types.Remote
cmd :: Command cmd :: Command
cmd = withOptions transferKeyOptions $ cmd = withOptions transferKeyOptions $ noCommit $
noCommit $ command "transferkey" paramKey seek SectionPlumbing command "transferkey" SectionPlumbing
"transfers a key from or to a remote" "transfers a key from or to a remote"
paramKey (withParams seek)
transferKeyOptions :: [Option] transferKeyOptions :: [Option]
transferKeyOptions = fileOption : fromToOptions transferKeyOptions = fileOption : fromToOptions
@ -26,7 +27,7 @@ transferKeyOptions = fileOption : fromToOptions
fileOption :: Option fileOption :: Option
fileOption = fieldOption [] "file" paramFile "the associated file" fileOption = fieldOption [] "file" paramFile "the associated file"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
to <- getOptionField toOption Remote.byNameWithUUID to <- getOptionField toOption Remote.byNameWithUUID
from <- getOptionField fromOption Remote.byNameWithUUID from <- getOptionField fromOption Remote.byNameWithUUID

View file

@ -22,10 +22,10 @@ import Git.Types (RemoteName)
data TransferRequest = TransferRequest Direction Remote Key AssociatedFile data TransferRequest = TransferRequest Direction Remote Key AssociatedFile
cmd :: Command cmd :: Command
cmd = command "transferkeys" paramNothing seek cmd = command "transferkeys" SectionPlumbing "transfers keys"
SectionPlumbing "transfers keys" paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
start :: CommandStart start :: CommandStart

View file

@ -17,13 +17,13 @@ import Logs.Group
import qualified Data.Set as S import qualified Data.Set as S
cmd :: Command cmd :: Command
cmd = command "trust" (paramRepeating paramRemote) seek cmd = command "trust" SectionSetup "trust a repository"
SectionSetup "trust a repository" (paramRepeating paramRemote) (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = trustCommand "trust" Trusted seek = trustCommand "trust" Trusted
trustCommand :: String -> TrustLevel -> CommandSeek trustCommand :: String -> TrustLevel -> CmdParams -> CommandSeek
trustCommand c level = withWords start trustCommand c level = withWords start
where where
start ws = do start ws = do

View file

@ -24,9 +24,9 @@ import Command.PreCommit (lockPreCommitHook)
cmd :: Command cmd :: Command
cmd = withOptions annexedMatchingOptions $ cmd = withOptions annexedMatchingOptions $
command "unannex" paramPaths SectionUtility command "unannex" SectionUtility
"undo accidential add command" "undo accidential add command"
(commandParser seek) paramPaths (withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek = wrapUnannex . (withFilesInGit $ whenAnnexed start) seek = wrapUnannex . (withFilesInGit $ whenAnnexed start)

View file

@ -23,10 +23,11 @@ import qualified Command.Sync
cmd :: Command cmd :: Command
cmd = notBareRepo $ cmd = notBareRepo $
command "undo" paramPaths seek command "undo" SectionCommon
SectionCommon "undo last change to a file or directory" "undo last change to a file or directory"
paramPaths (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
-- Safety first; avoid any undo that would touch files that are not -- Safety first; avoid any undo that would touch files that are not
-- in the index. -- in the index.

View file

@ -16,10 +16,10 @@ import Types.Group
import qualified Data.Set as S import qualified Data.Set as S
cmd :: Command cmd :: Command
cmd = command "ungroup" (paramPair paramRemote paramDesc) seek cmd = command "ungroup" SectionSetup "remove a repository from a group"
SectionSetup "remove a repository from a group" (paramPair paramRemote paramDesc) (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -22,9 +22,10 @@ import System.IO.HVFS
import System.IO.HVFS.Utils import System.IO.HVFS.Utils
cmd :: Command cmd :: Command
cmd = addCheck check $ command "uninit" paramPaths cmd = addCheck check $
SectionUtility "de-initialize git-annex and clean out repository" command "uninit" SectionUtility
(commandParser seek) "de-initialize git-annex and clean out repository"
paramPaths (withParams seek)
check :: Annex () check :: Annex ()
check = do check = do

View file

@ -20,10 +20,10 @@ editcmd :: Command
editcmd = mkcmd "edit" "same as unlock" editcmd = mkcmd "edit" "same as unlock"
mkcmd :: String -> String -> Command mkcmd :: String -> String -> Command
mkcmd n = notDirect . withOptions annexedMatchingOptions mkcmd n d = notDirect $ withOptions annexedMatchingOptions $
. command n paramPaths seek SectionCommon command n SectionCommon d paramPaths (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withFilesInGit $ whenAnnexed start seek = withFilesInGit $ whenAnnexed start
{- The unlock subcommand replaces the symlink with a copy of the file's {- The unlock subcommand replaces the symlink with a copy of the file's

View file

@ -12,8 +12,8 @@ import Types.TrustLevel
import Command.Trust (trustCommand) import Command.Trust (trustCommand)
cmd :: Command cmd :: Command
cmd = command "untrust" (paramRepeating paramRemote) seek cmd = command "untrust" SectionSetup "do not trust a repository"
SectionSetup "do not trust a repository" (paramRepeating paramRemote) (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = trustCommand "untrust" UnTrusted seek = trustCommand "untrust" UnTrusted

View file

@ -36,9 +36,9 @@ import Annex.BloomFilter
cmd :: Command cmd :: Command
cmd = withOptions [unusedFromOption, refSpecOption] $ cmd = withOptions [unusedFromOption, refSpecOption] $
command "unused" paramNothing command "unused" SectionMaintenance
SectionMaintenance "look for unused file content" "look for unused file content"
(commandParser seek) paramNothing (withParams seek)
unusedFromOption :: Option unusedFromOption :: Option
unusedFromOption = fieldOption ['f'] "from" paramRemote "remote to check for unused content" unusedFromOption = fieldOption ['f'] "from" paramRemote "remote to check for unused content"
@ -268,7 +268,7 @@ data UnusedMaps = UnusedMaps
, unusedTmpMap :: UnusedMap , unusedTmpMap :: UnusedMap
} }
withUnusedMaps :: (UnusedMaps -> Int -> CommandStart) -> CommandSeek withUnusedMaps :: (UnusedMaps -> Int -> CommandStart) -> CmdParams -> CommandSeek
withUnusedMaps a params = do withUnusedMaps a params = do
unused <- readUnusedMap "" unused <- readUnusedMap ""
unusedbad <- readUnusedMap "bad" unusedbad <- readUnusedMap "bad"

View file

@ -13,10 +13,10 @@ import Upgrade
cmd :: Command cmd :: Command
cmd = dontCheck repoExists $ -- because an old version may not seem to exist cmd = dontCheck repoExists $ -- because an old version may not seem to exist
command "upgrade" paramNothing seek command "upgrade" SectionMaintenance "upgrade repository layout"
SectionMaintenance "upgrade repository layout" paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
start :: CommandStart start :: CommandStart

View file

@ -13,10 +13,13 @@ import Annex.View
import Command.View (checkoutViewBranch) import Command.View (checkoutViewBranch)
cmd :: Command cmd :: Command
cmd = notBareRepo $ notDirect $ command "vadd" (paramRepeating "FIELD=GLOB") cmd = notBareRepo $ notDirect $
seek SectionMetaData "add subdirs to current view" command "vadd" SectionMetaData
"add subdirs to current view"
(paramRepeating "FIELD=GLOB")
(withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -16,10 +16,11 @@ import Command.View (checkoutViewBranch)
cmd :: Command cmd :: Command
cmd = notBareRepo $ notDirect $ cmd = notBareRepo $ notDirect $
command "vcycle" paramNothing seek SectionMetaData command "vcycle" SectionMetaData
"switch view to next layout" "switch view to next layout"
paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
start ::CommandStart start ::CommandStart

View file

@ -14,9 +14,10 @@ import Command.View (paramView, checkoutViewBranch)
cmd :: Command cmd :: Command
cmd = notBareRepo $ notDirect $ cmd = notBareRepo $ notDirect $
command "vfilter" paramView seek SectionMetaData "filter current view" command "vfilter" SectionMetaData "filter current view"
paramView (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -18,10 +18,10 @@ import Command.View (checkoutViewBranch)
cmd :: Command cmd :: Command
cmd = notBareRepo $ notDirect $ cmd = notBareRepo $ notDirect $
command "vpop" paramNumber seek SectionMetaData command "vpop" SectionMetaData "switch back to previous view"
"switch back to previous view" paramNumber (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart

View file

@ -20,12 +20,13 @@ import qualified Backend
cmd :: Command cmd :: Command
cmd = withOptions [rawOption] $ cmd = withOptions [rawOption] $
noCommit $ noRepo startNoRepo $ dontCheck repoExists $ noCommit $ noRepo startNoRepo $ dontCheck repoExists $
command "version" paramNothing seek SectionQuery "show version info" command "version" SectionQuery "show version info"
paramNothing (withParams seek)
rawOption :: Option rawOption :: Option
rawOption = flagOption [] "raw" "output only program version" rawOption = flagOption [] "raw" "output only program version"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing $ ifM (getOptionFlag rawOption) (startRaw, start) seek = withNothing $ ifM (getOptionFlag rawOption) (startRaw, start)
startRaw :: CommandStart startRaw :: CommandStart

View file

@ -30,10 +30,10 @@ import Types.ScheduledActivity
import Remote import Remote
cmd :: Command cmd :: Command
cmd = command "vicfg" paramNothing seek cmd = command "vicfg" SectionSetup "edit git-annex's configuration"
SectionSetup "edit git-annex's configuration" paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
start :: CommandStart start :: CommandStart

View file

@ -19,16 +19,17 @@ import Logs.View
cmd :: Command cmd :: Command
cmd = notBareRepo $ notDirect $ cmd = notBareRepo $ notDirect $
command "view" paramView seek SectionMetaData "enter a view branch" command "view" SectionMetaData "enter a view branch"
paramView (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart
start [] = error "Specify metadata to include in view" start [] = error "Specify metadata to include in view"
start params = do start ps = do
showStart "view" "" showStart "view" ""
view <- mkView params view <- mkView ps
go view =<< currentView go view =<< currentView
where where
go view Nothing = next $ perform view go view Nothing = next $ perform view
@ -45,11 +46,11 @@ paramView :: String
paramView = paramRepeating "FIELD=VALUE" paramView = paramRepeating "FIELD=VALUE"
mkView :: [String] -> Annex View mkView :: [String] -> Annex View
mkView params = go =<< inRepo Git.Branch.current mkView ps = go =<< inRepo Git.Branch.current
where where
go Nothing = error "not on any branch!" go Nothing = error "not on any branch!"
go (Just b) = return $ fst $ refineView (View b []) $ go (Just b) = return $ fst $ refineView (View b []) $
map parseViewParam $ reverse params map parseViewParam $ reverse ps
checkoutViewBranch :: View -> (View -> Annex Git.Branch) -> CommandCleanup checkoutViewBranch :: View -> (View -> Annex Git.Branch) -> CommandCleanup
checkoutViewBranch view mkbranch = do checkoutViewBranch view mkbranch = do

View file

@ -28,7 +28,7 @@ cmd'
-> Annex (M.Map UUID PreferredContentExpression) -> Annex (M.Map UUID PreferredContentExpression)
-> (UUID -> PreferredContentExpression -> Annex ()) -> (UUID -> PreferredContentExpression -> Annex ())
-> Command -> Command
cmd' name desc getter setter = command name pdesc seek SectionSetup desc cmd' name desc getter setter = command name SectionSetup desc pdesc (withParams seek)
where where
pdesc = paramPair paramRemote (paramOptional paramExpression) pdesc = paramPair paramRemote (paramOptional paramExpression)

View file

@ -14,9 +14,11 @@ import Utility.HumanTime
cmd :: Command cmd :: Command
cmd = notBareRepo $ withOptions [foregroundOption, stopOption] $ cmd = notBareRepo $ withOptions [foregroundOption, stopOption] $
command "watch" paramNothing seek SectionCommon "watch for changes and autocommit" command "watch" SectionCommon
"watch for changes and autocommit"
paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
stopdaemon <- getOptionFlag stopOption stopdaemon <- getOptionFlag stopOption
foreground <- getOptionFlag foregroundOption foreground <- getOptionFlag foregroundOption

View file

@ -40,13 +40,14 @@ import System.Environment (getArgs)
cmd :: Command cmd :: Command
cmd = withOptions [listenOption] $ cmd = withOptions [listenOption] $
noCommit $ noRepo startNoRepo $ dontCheck repoExists $ notBareRepo $ noCommit $ noRepo startNoRepo $ dontCheck repoExists $ notBareRepo $
command "webapp" paramNothing seek SectionCommon "launch webapp" command "webapp" SectionCommon "launch webapp"
paramNothing (withParams seek)
listenOption :: Option listenOption :: Option
listenOption = fieldOption [] "listen" paramAddress listenOption = fieldOption [] "listen" paramAddress
"accept connections to this address" "accept connections to this address"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
listenhost <- getOptionField listenOption return listenhost <- getOptionField listenOption return
withNothing (start listenhost) ps withNothing (start listenhost) ps

View file

@ -17,10 +17,11 @@ import Logs.Web
cmd :: Command cmd :: Command
cmd = noCommit $ withOptions (jsonOption : annexedMatchingOptions ++ keyOptions) $ cmd = noCommit $ withOptions (jsonOption : annexedMatchingOptions ++ keyOptions) $
command "whereis" paramPaths seek SectionQuery command "whereis" SectionQuery
"lists repositories that have file content" "lists repositories that have file content"
paramPaths (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
m <- remoteMap id m <- remoteMap id
withKeyOptions False withKeyOptions False

View file

@ -13,10 +13,10 @@ import Assistant.XMPP.Git
cmd :: Command cmd :: Command
cmd = noCommit $ noRepo startNoRepo $ dontCheck repoExists $ cmd = noCommit $ noRepo startNoRepo $ dontCheck repoExists $
command "xmppgit" paramNothing seek command "xmppgit" SectionPlumbing "git to XMPP relay"
SectionPlumbing "git to XMPP relay" paramNothing (withParams seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
start :: [String] -> CommandStart start :: [String] -> CommandStart