started converting to use optparse-applicative

This is a work in progress. It compiles and is able to do basic command
dispatch, including git autocorrection, while using optparse-applicative
for the core commandline parsing.

* Many commands are temporarily disabled before conversion.
* Options are not wired in yet.
* cmdnorepo actions don't work yet.

Also, removed the [Command] list, which was only used in one place.
This commit is contained in:
Joey Hess 2015-07-08 12:33:27 -04:00
parent 4018e5f6f1
commit a2ba701056
104 changed files with 435 additions and 370 deletions

View file

@ -1,6 +1,6 @@
{- git-annex command line parsing and dispatch {- git-annex command line parsing and dispatch
- -
- Copyright 2010-2012 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.
-} -}
@ -16,7 +16,7 @@ module CmdLine (
import qualified Control.Exception as E import qualified Control.Exception as E
import qualified Data.Map as M import qualified Data.Map as M
import Control.Exception (throw) import Control.Exception (throw)
import System.Console.GetOpt import qualified Options.Applicative as O
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
import System.Posix.Signals import System.Posix.Signals
#endif #endif
@ -35,6 +35,41 @@ import Types.Messages
dispatch :: Bool -> CmdParams -> [Command] -> [Option] -> [(String, String)] -> String -> IO Git.Repo -> IO () dispatch :: Bool -> CmdParams -> [Command] -> [Option] -> [(String, String)] -> String -> IO Git.Repo -> IO ()
dispatch fuzzyok allargs allcmds commonoptions fields header getgitrepo = do dispatch fuzzyok allargs allcmds commonoptions fields header getgitrepo = do
setupConsole setupConsole
go =<< (E.try getgitrepo :: IO (Either E.SomeException Git.Repo))
where
go (Right g) = do
state <- Annex.new g
Annex.eval state $ do
checkEnvironment
when fuzzy $
inRepo $ autocorrect . Just
forM_ fields $ uncurry Annex.setField
(cmd, seek) <- liftIO $
O.handleParseResult (parseCmd (name:args) allcmds)
when (cmdnomessages cmd) $
Annex.setOutput QuietOutput
-- TODO: propigate global options to annex state (how?)
whenM (annexDebug <$> Annex.getGitConfig) $
liftIO enableDebugOutput
startup
performCommandAction cmd seek $
shutdown $ cmdnocommit cmd
go (Left e) = do
when fuzzy $
autocorrect =<< Git.Config.global
-- a <- O.handleParseResult (parseCmd (name:args) allcmds)
error "TODO"
autocorrect = Git.AutoCorrect.prepare inputcmdname cmdname cmds
err msg = msg ++ "\n\n" ++ usage header allcmds
(fuzzy, cmds, inputcmdname, args) = findCmd fuzzyok allargs allcmds err
name
| fuzzy = case cmds of
[c] -> cmdname c
_ -> inputcmdname
| otherwise = inputcmdname
#if 0
case getOptCmd args cmd commonoptions of case getOptCmd args cmd commonoptions of
Right (flags, params) -> go flags params Right (flags, params) -> go flags params
=<< (E.try getgitrepo :: IO (Either E.SomeException Git.Repo)) =<< (E.try getgitrepo :: IO (Either E.SomeException Git.Repo))
@ -59,10 +94,19 @@ dispatch fuzzyok allargs allcmds commonoptions fields header getgitrepo = do
when fuzzy $ when fuzzy $
autocorrect =<< Git.Config.global autocorrect =<< Git.Config.global
maybe (throw e) (\a -> a params) (cmdnorepo cmd) maybe (throw e) (\a -> a params) (cmdnorepo cmd)
err msg = msg ++ "\n\n" ++ usage header allcmds
cmd = Prelude.head cmds cmd = Prelude.head cmds
(fuzzy, cmds, name, args) = findCmd fuzzyok allargs allcmds err #endif
autocorrect = Git.AutoCorrect.prepare name cmdname cmds
{- Parses command line and selects a command to run and gets the
- seek action for the command. -}
parseCmd :: CmdParams -> [Command] -> O.ParserResult (Command, CommandSeek)
parseCmd allargs allcmds = O.execParserPure (O.prefs O.idm) pinfo allargs
where
pinfo = O.info (O.subparser $ mconcat $ map mkcommand allcmds) O.idm
mkcommand c = O.command (cmdname c) (O.info (mkparser c) O.idm)
mkparser c = (,)
<$> pure c
<*> cmdparser c
{- Parses command line params far enough to find the Command to run, and {- Parses command line params far enough to find the Command to run, and
- returns the remaining params. - returns the remaining params.
@ -84,18 +128,6 @@ findCmd fuzzyok argv cmds err
Nothing -> [] Nothing -> []
Just n -> Git.AutoCorrect.fuzzymatches n cmdname cmds Just n -> Git.AutoCorrect.fuzzymatches n cmdname cmds
{- Parses command line options, and returns actions to run to configure flags
- and the remaining parameters for the command. -}
getOptCmd :: CmdParams -> Command -> [Option] -> Either String ([Annex ()], CmdParams)
getOptCmd argv cmd commonoptions = check $
getOpt Permute (commonoptions ++ cmdoptions cmd) argv
where
check (flags, rest, []) = Right (flags, rest)
check (_, _, errs) = Left $ unlines
[ concat errs
, commandUsage cmd
]
{- Actions to perform each time ran. -} {- Actions to perform each time ran. -}
startup :: Annex () startup :: Annex ()
startup = startup =

View file

@ -22,11 +22,11 @@ import Data.Either
{- Runs a command, starting with the check stage, and then {- Runs a command, starting with the check stage, and then
- the seek stage. Finishes by running the continutation, and - the seek stage. Finishes by running the continutation, and
- then showing a count of any failures. -} - then showing a count of any failures. -}
performCommandAction :: Command -> CmdParams -> Annex () -> Annex () performCommandAction :: Command -> CommandSeek -> Annex () -> Annex ()
performCommandAction Command { cmdseek = seek, cmdcheck = c, cmdname = name } params cont = do performCommandAction Command { cmdcheck = c, cmdname = name } seek cont = do
mapM_ runCheck c mapM_ runCheck c
Annex.changeState $ \s -> s { Annex.errcounter = 0 } Annex.changeState $ \s -> s { Annex.errcounter = 0 }
seek params seek
finishCommandActions finishCommandActions
cont cont
showerrcount =<< Annex.getState Annex.errcounter showerrcount =<< Annex.getState Annex.errcounter

View file

@ -16,6 +16,7 @@ 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
@ -116,15 +117,18 @@ 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 = concat 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
, Command.Copy.cmd , Command.Copy.cmd
, Command.Unlock.cmd , Command.Unlock.cmd
, Command.Unlock.editcmd
, Command.Lock.cmd , Command.Lock.cmd
, Command.Sync.cmd , Command.Sync.cmd
, Command.Mirror.cmd , Command.Mirror.cmd
@ -217,6 +221,7 @@ cmds = concat
, Command.FuzzTest.cmd , Command.FuzzTest.cmd
, Command.TestRemote.cmd , Command.TestRemote.cmd
#endif #endif
-}
] ]
header :: String header :: String

View file

@ -16,7 +16,6 @@ import qualified Git.Config
import CmdLine import CmdLine
import Command import Command
import Annex.UUID import Annex.UUID
import Annex (setField)
import CmdLine.GitAnnexShell.Fields import CmdLine.GitAnnexShell.Fields
import Utility.UserInfo import Utility.UserInfo
import Remote.GCrypt (getGCryptUUID) import Remote.GCrypt (getGCryptUUID)
@ -34,7 +33,7 @@ import qualified Command.NotifyChanges
import qualified Command.GCryptSetup import qualified Command.GCryptSetup
cmds_readonly :: [Command] cmds_readonly :: [Command]
cmds_readonly = concat cmds_readonly =
[ gitAnnexShellCheck Command.ConfigList.cmd [ gitAnnexShellCheck Command.ConfigList.cmd
, gitAnnexShellCheck Command.InAnnex.cmd , gitAnnexShellCheck Command.InAnnex.cmd
, gitAnnexShellCheck Command.SendKey.cmd , gitAnnexShellCheck Command.SendKey.cmd
@ -43,7 +42,7 @@ cmds_readonly = concat
] ]
cmds_notreadonly :: [Command] cmds_notreadonly :: [Command]
cmds_notreadonly = concat cmds_notreadonly =
[ gitAnnexShellCheck Command.RecvKey.cmd [ gitAnnexShellCheck Command.RecvKey.cmd
, gitAnnexShellCheck Command.DropKey.cmd , gitAnnexShellCheck Command.DropKey.cmd
, gitAnnexShellCheck Command.Commit.cmd , gitAnnexShellCheck Command.Commit.cmd
@ -100,12 +99,10 @@ builtin cmd dir params = do
checkNotReadOnly cmd checkNotReadOnly cmd
checkDirectory $ Just dir checkDirectory $ Just dir
let (params', fieldparams, opts) = partitionParams params let (params', fieldparams, opts) = partitionParams params
fields = filter checkField $ parseFields fieldparams rsyncopts = ("RsyncOptions", unwords opts)
cmds' = map (newcmd $ unwords opts) cmds fields = rsyncopts : filter checkField (parseFields fieldparams)
dispatch False (cmd : params') cmds' options fields header mkrepo dispatch False (cmd : params') cmds options fields header mkrepo
where where
addrsyncopts opts seek k = setField "RsyncOptions" opts >> seek k
newcmd opts c = c { cmdseek = addrsyncopts opts (cmdseek c) }
mkrepo = do mkrepo = do
r <- Git.Construct.repoAbsPath dir >>= Git.Construct.fromAbsPath r <- Git.Construct.repoAbsPath dir >>= Git.Construct.fromAbsPath
Git.Config.read r Git.Config.read r
@ -200,8 +197,8 @@ checkEnv var = do
{- Modifies a Command to check that it is run in either a git-annex {- Modifies a Command to check that it is run in either a git-annex
- repository, or a repository with a gcrypt-id set. -} - repository, or a repository with a gcrypt-id set. -}
gitAnnexShellCheck :: [Command] -> [Command] gitAnnexShellCheck :: Command -> Command
gitAnnexShellCheck = map $ addCheck okforshell . dontCheck repoExists gitAnnexShellCheck = addCheck okforshell . dontCheck repoExists
where where
okforshell = unlessM (isInitialized <||> isJust . gcryptId <$> Annex.getGitConfig) $ okforshell = unlessM (isInitialized <||> isJust . gcryptId <$> Annex.getGitConfig) $
error "Not a git-annex or gcrypt repository." error "Not a git-annex or gcrypt repository."

View file

@ -29,11 +29,11 @@ import Logs.Unused
import Annex.CatFile import Annex.CatFile
import Annex.Content import Annex.Content
withFilesInGit :: (FilePath -> CommandStart) -> CommandSeek withFilesInGit :: (FilePath -> CommandStart) -> CmdParams -> CommandSeek
withFilesInGit a params = seekActions $ prepFiltered a $ withFilesInGit a params = seekActions $ prepFiltered a $
seekHelper LsFiles.inRepo params seekHelper LsFiles.inRepo params
withFilesInGitNonRecursive :: (FilePath -> CommandStart) -> CommandSeek withFilesInGitNonRecursive :: (FilePath -> CommandStart) -> CmdParams -> CommandSeek
withFilesInGitNonRecursive a params = ifM (Annex.getState Annex.force) withFilesInGitNonRecursive a params = ifM (Annex.getState Annex.force)
( withFilesInGit a params ( withFilesInGit a params
, if null params , if null params
@ -54,7 +54,7 @@ withFilesInGitNonRecursive a params = ifM (Annex.getState Annex.force)
_ -> needforce _ -> needforce
needforce = error "Not recursively setting metadata. Use --force to do that." needforce = error "Not recursively setting metadata. Use --force to do that."
withFilesNotInGit :: Bool -> (FilePath -> CommandStart) -> CommandSeek withFilesNotInGit :: Bool -> (FilePath -> CommandStart) -> CmdParams -> CommandSeek
withFilesNotInGit skipdotfiles a params withFilesNotInGit skipdotfiles a params
| skipdotfiles = do | skipdotfiles = do
{- dotfiles are not acted on unless explicitly listed -} {- dotfiles are not acted on unless explicitly listed -}
@ -73,7 +73,7 @@ withFilesNotInGit skipdotfiles a params
go l = seekActions $ prepFiltered a $ go l = seekActions $ prepFiltered a $
return $ concat $ segmentPaths params l return $ concat $ segmentPaths params l
withFilesInRefs :: (FilePath -> Key -> CommandStart) -> CommandSeek withFilesInRefs :: (FilePath -> Key -> CommandStart) -> CmdParams -> CommandSeek
withFilesInRefs a = mapM_ go withFilesInRefs a = mapM_ go
where where
go r = do go r = do
@ -87,7 +87,7 @@ withFilesInRefs a = mapM_ go
Just k -> whenM (matcher $ MatchingKey k) $ Just k -> whenM (matcher $ MatchingKey k) $
commandAction $ a f k commandAction $ a f k
withPathContents :: ((FilePath, FilePath) -> CommandStart) -> CommandSeek withPathContents :: ((FilePath, FilePath) -> CommandStart) -> CmdParams -> CommandSeek
withPathContents a params = do withPathContents a params = do
matcher <- Limit.getMatcher matcher <- Limit.getMatcher
seekActions $ map a <$> (filterM (checkmatch matcher) =<< ps) seekActions $ map a <$> (filterM (checkmatch matcher) =<< ps)
@ -103,27 +103,27 @@ withPathContents a params = do
, matchFile = relf , matchFile = relf
} }
withWords :: ([String] -> CommandStart) -> CommandSeek withWords :: ([String] -> CommandStart) -> CmdParams -> CommandSeek
withWords a params = seekActions $ return [a params] withWords a params = seekActions $ return [a params]
withStrings :: (String -> CommandStart) -> CommandSeek withStrings :: (String -> CommandStart) -> CmdParams -> CommandSeek
withStrings a params = seekActions $ return $ map a params withStrings a params = seekActions $ return $ map a params
withPairs :: ((String, String) -> CommandStart) -> CommandSeek withPairs :: ((String, String) -> CommandStart) -> CmdParams -> CommandSeek
withPairs a params = seekActions $ return $ map a $ pairs [] params withPairs a params = seekActions $ return $ map a $ pairs [] params
where where
pairs c [] = reverse c pairs c [] = reverse c
pairs c (x:y:xs) = pairs ((x,y):c) xs pairs c (x:y:xs) = pairs ((x,y):c) xs
pairs _ _ = error "expected pairs" pairs _ _ = error "expected pairs"
withFilesToBeCommitted :: (String -> CommandStart) -> CommandSeek withFilesToBeCommitted :: (String -> CommandStart) -> CmdParams -> CommandSeek
withFilesToBeCommitted a params = seekActions $ prepFiltered a $ withFilesToBeCommitted a params = seekActions $ prepFiltered a $
seekHelper LsFiles.stagedNotDeleted params seekHelper LsFiles.stagedNotDeleted params
withFilesUnlocked :: (FilePath -> CommandStart) -> CommandSeek withFilesUnlocked :: (FilePath -> CommandStart) -> CmdParams -> CommandSeek
withFilesUnlocked = withFilesUnlocked' LsFiles.typeChanged withFilesUnlocked = withFilesUnlocked' LsFiles.typeChanged
withFilesUnlockedToBeCommitted :: (FilePath -> CommandStart) -> CommandSeek withFilesUnlockedToBeCommitted :: (FilePath -> CommandStart) -> CmdParams -> CommandSeek
withFilesUnlockedToBeCommitted = withFilesUnlocked' LsFiles.typeChangedStaged withFilesUnlockedToBeCommitted = withFilesUnlocked' LsFiles.typeChangedStaged
{- Unlocked files have changed type from a symlink to a regular file. {- Unlocked files have changed type from a symlink to a regular file.
@ -131,7 +131,7 @@ withFilesUnlockedToBeCommitted = withFilesUnlocked' LsFiles.typeChangedStaged
- Furthermore, unlocked files used to be a git-annex symlink, - Furthermore, unlocked files used to be a git-annex symlink,
- not some other sort of symlink. - not some other sort of symlink.
-} -}
withFilesUnlocked' :: ([FilePath] -> Git.Repo -> IO ([FilePath], IO Bool)) -> (FilePath -> CommandStart) -> CommandSeek withFilesUnlocked' :: ([FilePath] -> Git.Repo -> IO ([FilePath], IO Bool)) -> (FilePath -> CommandStart) -> CmdParams -> CommandSeek
withFilesUnlocked' typechanged a params = seekActions $ withFilesUnlocked' typechanged a params = seekActions $
prepFiltered a unlockedfiles prepFiltered a unlockedfiles
where where
@ -142,11 +142,11 @@ isUnlocked f = liftIO (notSymlink f) <&&>
(isJust <$> catKeyFile f <||> isJust <$> catKeyFileHEAD f) (isJust <$> catKeyFile f <||> isJust <$> catKeyFileHEAD f)
{- Finds files that may be modified. -} {- Finds files that may be modified. -}
withFilesMaybeModified :: (FilePath -> CommandStart) -> CommandSeek withFilesMaybeModified :: (FilePath -> CommandStart) -> CmdParams -> CommandSeek
withFilesMaybeModified a params = seekActions $ withFilesMaybeModified a params = seekActions $
prepFiltered a $ seekHelper LsFiles.modified params prepFiltered a $ seekHelper LsFiles.modified params
withKeys :: (Key -> CommandStart) -> CommandSeek withKeys :: (Key -> CommandStart) -> CmdParams -> CommandSeek
withKeys a params = seekActions $ return $ map (a . parse) params withKeys a params = seekActions $ return $ map (a . parse) params
where where
parse p = fromMaybe (error "bad key") $ file2key p parse p = fromMaybe (error "bad key") $ file2key p
@ -160,7 +160,7 @@ getOptionField option converter = converter <=< Annex.getField $ optionName opti
getOptionFlag :: Option -> Annex Bool getOptionFlag :: Option -> Annex Bool
getOptionFlag option = Annex.getFlag (optionName option) getOptionFlag option = Annex.getFlag (optionName option)
withNothing :: CommandStart -> CommandSeek withNothing :: CommandStart -> CmdParams -> CommandSeek
withNothing a [] = seekActions $ return [a] withNothing a [] = seekActions $ return [a]
withNothing _ _ = error "This command takes no parameters." withNothing _ _ = error "This command takes no parameters."
@ -171,7 +171,7 @@ withNothing _ _ = error "This command takes no parameters."
- -
- Otherwise falls back to a regular CommandSeek action on - Otherwise falls back to a regular CommandSeek action on
- whatever params were passed. -} - whatever params were passed. -}
withKeyOptions :: Bool -> (Key -> CommandStart) -> CommandSeek -> CommandSeek withKeyOptions :: Bool -> (Key -> CommandStart) -> (CmdParams -> CommandSeek) -> CmdParams -> CommandSeek
withKeyOptions auto keyop = withKeyOptions' auto $ \getkeys -> do withKeyOptions auto keyop = withKeyOptions' auto $ \getkeys -> do
matcher <- Limit.getMatcher matcher <- Limit.getMatcher
seekActions $ map (process matcher) <$> getkeys seekActions $ map (process matcher) <$> getkeys
@ -181,7 +181,7 @@ withKeyOptions auto keyop = withKeyOptions' auto $ \getkeys -> do
, return Nothing , return Nothing
) )
withKeyOptions' :: Bool -> (Annex [Key] -> Annex ()) -> CommandSeek -> CommandSeek withKeyOptions' :: Bool -> (Annex [Key] -> Annex ()) -> (CmdParams -> CommandSeek) -> CmdParams -> CommandSeek
withKeyOptions' auto keyop fallbackop params = do withKeyOptions' auto keyop fallbackop params = do
bare <- fromRepo Git.repoIsLocalBare bare <- fromRepo Git.repoIsLocalBare
allkeys <- Annex.getFlag "all" allkeys <- Annex.getFlag "all"

View file

@ -7,6 +7,7 @@
module Command ( module Command (
command, command,
commandParser,
noRepo, noRepo,
noCommit, noCommit,
noMessages, noMessages,
@ -32,10 +33,17 @@ 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
{- Generates a normal command -} import qualified Options.Applicative as O
command :: String -> String -> CommandSeek -> CommandSection -> String -> Command
{- Generates a normal Command -}
command :: String -> String -> CommandSection -> String -> CommandParser -> Command
command = Command [] Nothing commonChecks False False command = Command [] Nothing commonChecks False False
{- Simple CommandParser generator, for when the CommandSeek wants all
- non-option parameters. -}
commandParser :: (CmdParams -> CommandSeek) -> CommandParser
commandParser mkseek = mkseek <$> O.many (O.argument O.str O.idm)
{- 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. -}
noCommit :: Command -> Command noCommit :: Command -> Command

View file

@ -34,9 +34,10 @@ import Utility.Tmp
import Control.Exception (IOException) import Control.Exception (IOException)
cmd :: [Command] cmd :: Command
cmd = [notBareRepo $ withOptions addOptions $ cmd = notBareRepo $ withOptions addOptions $
command "add" paramPaths seek SectionCommon "add files to annex"] command "add" paramPaths SectionCommon "add files to annex"
(commandParser seek)
addOptions :: [Option] addOptions :: [Option]
addOptions = includeDotFilesOption : fileMatchingOptions addOptions = includeDotFilesOption : fileMatchingOptions
@ -47,7 +48,7 @@ includeDotFilesOption = flagOption [] "include-dotfiles" "don't skip dotfiles"
{- Add acts on both files not checked into git yet, and unlocked files. {- Add acts on both files not checked into git yet, and unlocked files.
- -
- In direct mode, it acts on any files that have changed. -} - In direct mode, it acts on any files that have changed. -}
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
matcher <- largeFilesMatcher matcher <- largeFilesMatcher
let go a = flip a ps $ \file -> ifM (checkFileMatcher matcher file <||> Annex.getState Annex.force) let go a = flip a ps $ \file -> ifM (checkFileMatcher matcher file <||> Annex.getState Annex.force)

View file

@ -14,9 +14,9 @@ import qualified Command.Add
import Command.Unused (withUnusedMaps, UnusedMaps(..), startUnused) import Command.Unused (withUnusedMaps, UnusedMaps(..), startUnused)
import Types.Key import Types.Key
cmd :: [Command] cmd :: Command
cmd = [notDirect $ command "addunused" (paramRepeating paramNumRange) cmd = notDirect $ command "addunused" (paramRepeating paramNumRange)
seek SectionMaintenance "add back unused files"] seek SectionMaintenance "add back unused files"
seek :: CommandSeek seek :: CommandSeek
seek = withUnusedMaps start seek = withUnusedMaps start

View file

@ -37,10 +37,10 @@ import Annex.Quvi
import qualified Utility.Quvi as Quvi import qualified Utility.Quvi as Quvi
#endif #endif
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" (paramRepeating paramUrl) seek
SectionCommon "add urls to annex"] SectionCommon "add urls to annex"
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"

View file

@ -19,10 +19,10 @@ import Assistant.Install
import System.Environment 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" paramNothing seek SectionCommon
"automatically sync changes"] "automatically sync changes"
options :: [Option] options :: [Option]
options = options =

View file

@ -14,9 +14,9 @@ import qualified Remote
import Annex import Annex
import Types.Messages import Types.Messages
cmd :: [Command] cmd :: Command
cmd = [noCommit $ command "checkpresentkey" (paramPair paramKey paramRemote) seek cmd = noCommit $ command "checkpresentkey" (paramPair paramKey paramRemote) seek
SectionPlumbing "check if key is present in remote"] SectionPlumbing "check if key is present in remote"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

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

View file

@ -15,11 +15,12 @@ import qualified Annex.Branch
import qualified Git.Config import qualified Git.Config
import Remote.GCrypt (coreGCryptId) import Remote.GCrypt (coreGCryptId)
cmd :: [Command] cmd :: Command
cmd = [noCommit $ command "configlist" paramNothing seek cmd = noCommit $ command "configlist" paramNothing
SectionPlumbing "outputs relevant git configuration"] SectionPlumbing "outputs relevant git configuration"
(commandParser seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
start :: CommandStart start :: CommandStart

View file

@ -12,10 +12,10 @@ import Command
import CmdLine.Batch import CmdLine.Batch
import Annex.Content import Annex.Content
cmd :: [Command] cmd :: Command
cmd = [withOptions [batchOption] $ noCommit $ noMessages $ cmd = withOptions [batchOption] $ noCommit $ noMessages $
command "contentlocation" (paramRepeating paramKey) seek command "contentlocation" (paramRepeating paramKey) seek
SectionPlumbing "looks up content for a key"] SectionPlumbing "looks up content for a key"
seek :: CommandSeek seek :: CommandSeek
seek = batchable withKeys start seek = batchable withKeys start

View file

@ -14,9 +14,9 @@ import qualified Remote
import Annex.Wanted import Annex.Wanted
import Annex.NumCopies import Annex.NumCopies
cmd :: [Command] cmd :: Command
cmd = [withOptions copyOptions $ command "copy" paramPaths seek cmd = withOptions copyOptions $ command "copy" paramPaths seek
SectionCommon "copy content of files to/from another repository"] SectionCommon "copy content of files to/from another repository"
copyOptions :: [Option] copyOptions :: [Option]
copyOptions = Command.Move.moveOptions ++ [autoOption] copyOptions = Command.Move.moveOptions ++ [autoOption]

View file

@ -16,10 +16,10 @@ import Command.Trust (trustCommand)
import Logs.Location import Logs.Location
import Remote (keyLocations) import Remote (keyLocations)
cmd :: [Command] cmd :: Command
cmd = [withOptions [keyOption] $ cmd = withOptions [keyOption] $
command "dead" (paramRepeating paramRemote) seek command "dead" (paramRepeating paramRemote) seek
SectionSetup "hide a lost repository or key"] SectionSetup "hide a lost repository or key"
seek :: CommandSeek seek :: CommandSeek
seek ps = maybe (trustCommand "dead" DeadTrusted ps) (flip seekKey ps) seek ps = maybe (trustCommand "dead" DeadTrusted ps) (flip seekKey ps)

View file

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

View file

@ -13,10 +13,10 @@ import Annex.Content
import Annex.Link import Annex.Link
import Git.Types import Git.Types
cmd :: [Command] cmd :: Command
cmd = [dontCheck repoExists $ cmd = dontCheck repoExists $
command "diffdriver" ("[-- cmd --]") seek command "diffdriver" ("[-- cmd --]") seek
SectionPlumbing "external git diff driver shim"] SectionPlumbing "external git diff driver shim"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -15,10 +15,10 @@ import qualified Git.Branch
import Config import Config
import Annex.Direct import Annex.Direct
cmd :: [Command] cmd :: Command
cmd = [notBareRepo $ noDaemonRunning $ cmd = notBareRepo $ noDaemonRunning $
command "direct" paramNothing seek command "direct" paramNothing seek
SectionSetup "switch repository to direct mode"] SectionSetup "switch repository to direct mode"
seek :: CommandSeek seek :: CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -22,9 +22,9 @@ 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) $ command "drop" paramPaths seek
SectionCommon "indicate content of files not currently wanted"] SectionCommon "indicate content of files not currently wanted"
dropOptions :: [Option] dropOptions :: [Option]
dropOptions = dropFromOption : annexedMatchingOptions ++ [autoOption] ++ keyOptions dropOptions = dropFromOption : annexedMatchingOptions ++ [autoOption] ++ keyOptions

View file

@ -13,11 +13,12 @@ import qualified Annex
import Logs.Location import Logs.Location
import Annex.Content import Annex.Content
cmd :: [Command] cmd :: Command
cmd = [noCommit $ command "dropkey" (paramRepeating paramKey) seek cmd = noCommit $ command "dropkey" (paramRepeating paramKey)
SectionPlumbing "drops annexed content for specified keys"] SectionPlumbing "drops annexed content for specified keys"
(commandParser seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withKeys start seek = withKeys start
start :: Key -> CommandStart start :: Key -> CommandStart

View file

@ -16,10 +16,10 @@ import qualified Git
import Command.Unused (withUnusedMaps, UnusedMaps(..), startUnused) import Command.Unused (withUnusedMaps, UnusedMaps(..), startUnused)
import Annex.NumCopies import Annex.NumCopies
cmd :: [Command] cmd :: Command
cmd = [withOptions [Command.Drop.dropFromOption] $ cmd = withOptions [Command.Drop.dropFromOption] $
command "dropunused" (paramRepeating paramNumRange) command "dropunused" (paramRepeating paramNumRange)
seek SectionMaintenance "drop unused file content"] seek SectionMaintenance "drop unused file content"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do

View file

@ -15,10 +15,10 @@ 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"
(paramPair paramName $ paramOptional $ paramRepeating paramKeyValue) (paramPair paramName $ paramOptional $ paramRepeating paramKeyValue)
seek SectionSetup "enables use of an existing special remote"] seek SectionSetup "enables use of an existing special remote"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -14,10 +14,10 @@ import qualified Utility.Format
import Command.Find (formatOption, getFormat, showFormatted, keyVars) import Command.Find (formatOption, getFormat, showFormatted, keyVars)
import Types.Key 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" (paramRepeating paramKey) seek
SectionPlumbing "prints information from a key"] SectionPlumbing "prints information from a key"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do

View file

@ -20,9 +20,9 @@ import Utility.HumanTime
import Data.Time.Clock.POSIX 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] $ command "expire" paramExpire seek
SectionMaintenance "expire inactive repositories"] SectionMaintenance "expire inactive repositories"
paramExpire :: String paramExpire :: String
paramExpire = (paramRepeating $ paramOptional paramRemote ++ ":" ++ paramTime) paramExpire = (paramRepeating $ paramOptional paramRemote ++ ":" ++ paramTime)

View file

@ -19,9 +19,9 @@ import qualified Utility.Format
import Utility.DataUnits import Utility.DataUnits
import Types.Key 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" paramPaths seek SectionQuery "lists available files"
mkCommand :: Command -> Command mkCommand :: Command -> Command
mkCommand = noCommit . noMessages . withOptions [formatOption, print0Option, jsonOption] mkCommand = noCommit . noMessages . withOptions [formatOption, print0Option, jsonOption]

View file

@ -10,10 +10,10 @@ module Command.FindRef where
import Command import Command
import qualified Command.Find as Find 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" paramRef seek SectionPlumbing
"lists files in a git ref"] "lists files in a git ref"
seek :: CommandSeek seek :: CommandSeek
seek refs = do seek refs = do

View file

@ -18,12 +18,13 @@ import Utility.Touch
#endif #endif
#endif #endif
cmd :: [Command] cmd :: Command
cmd = [notDirect $ noCommit $ withOptions annexedMatchingOptions $ cmd = notDirect $ noCommit $ withOptions annexedMatchingOptions $
command "fix" paramPaths seek command "fix" paramPaths
SectionMaintenance "fix up symlinks to point to annexed content"] SectionMaintenance "fix up symlinks to point to annexed content"
(commandParser seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withFilesInGit $ whenAnnexed start seek = withFilesInGit $ whenAnnexed start
{- Fixes the symlink to an annexed file. -} {- Fixes the symlink to an annexed file. -}

View file

@ -15,9 +15,9 @@ 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 $ command "forget" paramNothing seek
SectionMaintenance "prune git-annex branch history"] SectionMaintenance "prune git-annex branch history"
forgetOptions :: [Option] forgetOptions :: [Option]
forgetOptions = [dropDeadOption] forgetOptions = [dropDeadOption]

View file

@ -19,10 +19,10 @@ import qualified Backend.URL
import Network.URI import Network.URI
cmd :: [Command] cmd :: Command
cmd = [notDirect $ notBareRepo $ cmd = notDirect $ notBareRepo $
command "fromkey" (paramPair paramKey paramPath) seek command "fromkey" (paramPair paramKey paramPath) seek
SectionPlumbing "adds a file using a specific key"] SectionPlumbing "adds a file using a specific key"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do

View file

@ -40,9 +40,9 @@ import qualified Database.Fsck as FsckDb
import Data.Time.Clock.POSIX 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 $ command "fsck" paramPaths seek
SectionMaintenance "check for problems"] SectionMaintenance "check for problems"
fsckFromOption :: Option fsckFromOption :: Option
fsckFromOption = fieldOption ['f'] "from" paramRemote "check remote" fsckFromOption = fieldOption ['f'] "from" paramRemote "check remote"

View file

@ -20,9 +20,9 @@ import System.Random (getStdRandom, random, randomR)
import Test.QuickCheck import Test.QuickCheck
import Control.Concurrent import Control.Concurrent
cmd :: [Command] cmd :: Command
cmd = [ notBareRepo $ command "fuzztest" paramNothing seek SectionTesting cmd = notBareRepo $ command "fuzztest" paramNothing seek SectionTesting
"generates fuzz test files"] "generates fuzz test files"
seek :: CommandSeek seek :: CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -13,12 +13,13 @@ import Annex.UUID
import qualified Remote.GCrypt import qualified Remote.GCrypt
import qualified Git import qualified Git
cmd :: [Command] cmd :: Command
cmd = [dontCheck repoExists $ noCommit $ cmd = dontCheck repoExists $ noCommit $
command "gcryptsetup" paramValue seek command "gcryptsetup" paramValue
SectionPlumbing "sets up gcrypt repository"] SectionPlumbing "sets up gcrypt repository"
(commandParser seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withStrings start seek = withStrings start
start :: String -> CommandStart start :: String -> CommandStart

View file

@ -16,9 +16,9 @@ import Annex.NumCopies
import Annex.Wanted 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 $ command "get" paramPaths seek
SectionCommon "make content of annexed files available"] SectionCommon "make content of annexed files available"
getOptions :: [Option] getOptions :: [Option]
getOptions = fromOption : autoOption : jobsOption : annexedMatchingOptions getOptions = fromOption : autoOption : jobsOption : annexedMatchingOptions

View file

@ -15,9 +15,9 @@ 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" (paramPair paramRemote paramDesc) seek
SectionSetup "add a repository to a group"] SectionSetup "add a repository to a group"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -12,9 +12,9 @@ import Command
import Logs.PreferredContent 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" (paramPair paramGroup (paramOptional paramExpression)) seek
SectionSetup "get or set groupwanted expression"] SectionSetup "get or set groupwanted expression"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -21,9 +21,9 @@ import qualified Command.Fsck
import System.Console.GetOpt import System.Console.GetOpt
cmd :: [Command] cmd :: Command
cmd = [noCommit $ noRepo startNoRepo $ dontCheck repoExists $ cmd = noCommit $ noRepo startNoRepo $ dontCheck repoExists $
command "help" (paramOptional "COMMAND") seek SectionCommon "display help"] command "help" (paramOptional "COMMAND") seek SectionCommon "display help"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -22,9 +22,9 @@ import Annex.NumCopies
import Types.TrustLevel 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 $ command "import" paramPaths seek
SectionCommon "move and add files from outside git working copy"] SectionCommon "move and add files from outside git working copy"
opts :: [Option] opts :: [Option]
opts = duplicateModeOptions ++ fileMatchingOptions opts = duplicateModeOptions ++ fileMatchingOptions

View file

@ -43,10 +43,10 @@ import Types.MetaData
import Logs.MetaData import Logs.MetaData
import Annex.MetaData 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" (paramRepeating paramUrl) seek
SectionCommon "import files from podcast feeds"] SectionCommon "import files from podcast feeds"
templateOption :: Option templateOption :: Option
templateOption = fieldOption [] "template" paramFormat "template for filenames" templateOption = fieldOption [] "template" paramFormat "template for filenames"

View file

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

View file

@ -22,10 +22,10 @@ import Annex.CatFile
import Annex.Init import Annex.Init
import qualified Command.Add import qualified Command.Add
cmd :: [Command] cmd :: Command
cmd = [notBareRepo $ noDaemonRunning $ cmd = notBareRepo $ noDaemonRunning $
command "indirect" paramNothing seek command "indirect" paramNothing seek
SectionSetup "switch repository to indirect mode"] SectionSetup "switch repository to indirect mode"
seek :: CommandSeek seek :: CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -78,10 +78,10 @@ emptyStatInfo = StatInfo Nothing Nothing M.empty Nothing
-- a state monad for running Stats in -- a state monad for running Stats in
type StatState = StateT StatInfo Annex 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" (paramOptional $ paramRepeating paramItem) seek SectionQuery command "info" (paramOptional $ paramRepeating paramItem) seek 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"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -11,9 +11,9 @@ import Common.Annex
import Command import Command
import Annex.Init import Annex.Init
cmd :: [Command] cmd :: Command
cmd = [dontCheck repoExists $ cmd = dontCheck repoExists $
command "init" paramDesc seek SectionSetup "initialize git-annex"] command "init" paramDesc seek SectionSetup "initialize git-annex"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -19,10 +19,10 @@ import Logs.Trust
import Data.Ord import Data.Ord
cmd :: [Command] cmd :: Command
cmd = [command "initremote" cmd = command "initremote"
(paramPair paramName $ paramOptional $ paramRepeating paramKeyValue) (paramPair paramName $ paramOptional $ paramRepeating paramKeyValue)
seek SectionSetup "creates a special (non-git) remote"] seek SectionSetup "creates a special (non-git) remote"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -23,10 +23,10 @@ import Annex.UUID
import qualified Annex import qualified Annex
import Git.Types (RemoteName) import Git.Types (RemoteName)
cmd :: [Command] cmd :: Command
cmd = [noCommit $ withOptions (allrepos : annexedMatchingOptions) $ cmd = noCommit $ withOptions (allrepos : annexedMatchingOptions) $
command "list" paramPaths seek command "list" paramPaths seek
SectionQuery "show which remotes contain files"] SectionQuery "show which remotes contain files"
allrepos :: Option allrepos :: Option
allrepos = flagOption [] "allrepos" "show all repositories, not only remotes" allrepos = flagOption [] "allrepos" "show all repositories, not only remotes"

View file

@ -12,10 +12,10 @@ import Command
import qualified Annex.Queue import qualified Annex.Queue
import qualified Annex import qualified Annex
cmd :: [Command] cmd :: Command
cmd = [notDirect $ withOptions annexedMatchingOptions $ cmd = notDirect $ withOptions annexedMatchingOptions $
command "lock" paramPaths seek SectionCommon command "lock" paramPaths seek SectionCommon
"undo unlock command"] "undo unlock command"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do

View file

@ -38,9 +38,9 @@ data RefChange = RefChange
type Outputter = Bool -> POSIXTime -> [UUID] -> Annex () 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" paramPaths seek SectionQuery "shows location log"
options :: [Option] options :: [Option]
options = passthruOptions ++ [gourceOption] ++ annexedMatchingOptions options = passthruOptions ++ [gourceOption] ++ annexedMatchingOptions

View file

@ -13,10 +13,10 @@ import CmdLine.Batch
import Annex.CatFile import Annex.CatFile
import Types.Key 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" (paramRepeating paramFile) seek
SectionPlumbing "looks up key used for file"] SectionPlumbing "looks up key used for file"
seek :: CommandSeek seek :: CommandSeek
seek = batchable withStrings start seek = batchable withStrings start

View file

@ -25,10 +25,10 @@ import qualified Utility.Dot as Dot
-- a link from the first repository to the second (its remote) -- a link from the first repository to the second (its remote)
data Link = Link Git.Repo Git.Repo data Link = Link Git.Repo Git.Repo
cmd :: [Command] cmd :: Command
cmd = [dontCheck repoExists $ cmd = dontCheck repoExists $
command "map" paramNothing seek SectionQuery command "map" paramNothing seek SectionQuery
"generate map of repositories"] "generate map of repositories"
seek :: CommandSeek seek :: CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -13,9 +13,9 @@ import qualified Annex.Branch
import qualified Git.Branch 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" paramNothing seek SectionMaintenance
"automatically merge changes from remotes"] "automatically merge changes from remotes"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do

View file

@ -16,10 +16,10 @@ import Logs.MetaData
import qualified Data.Set as S import qualified Data.Set as S
import Data.Time.Clock.POSIX import Data.Time.Clock.POSIX
cmd :: [Command] cmd :: Command
cmd = [withOptions metaDataOptions $ cmd = withOptions metaDataOptions $
command "metadata" paramPaths seek command "metadata" paramPaths seek
SectionMetaData "sets or gets metadata of a file"] SectionMetaData "sets or gets metadata of a file"
metaDataOptions :: [Option] metaDataOptions :: [Option]
metaDataOptions = metaDataOptions =

View file

@ -18,10 +18,10 @@ import qualified Command.ReKey
import qualified Command.Fsck import qualified Command.Fsck
import qualified Annex import qualified Annex
cmd :: [Command] cmd :: Command
cmd = [notDirect $ withOptions annexedMatchingOptions $ cmd = notDirect $ withOptions annexedMatchingOptions $
command "migrate" paramPaths seek command "migrate" paramPaths seek
SectionUtility "switch data to different backend"] SectionUtility "switch data to different backend"
seek :: CommandSeek seek :: CommandSeek
seek = withFilesInGit $ whenAnnexed start seek = withFilesInGit $ whenAnnexed start

View file

@ -16,9 +16,9 @@ import qualified Remote
import Annex.Content import Annex.Content
import Annex.NumCopies import Annex.NumCopies
cmd :: [Command] cmd :: Command
cmd = [withOptions mirrorOptions $ command "mirror" paramPaths seek cmd = withOptions mirrorOptions $ command "mirror" paramPaths seek
SectionCommon "mirror content of files to/from another repository"] SectionCommon "mirror content of files to/from another repository"
mirrorOptions :: [Option] mirrorOptions :: [Option]
mirrorOptions = fromToOptions ++ [jobsOption] ++ annexedMatchingOptions ++ keyOptions mirrorOptions = fromToOptions ++ [jobsOption] ++ annexedMatchingOptions ++ keyOptions

View file

@ -17,9 +17,9 @@ import Annex.UUID
import Annex.Transfer import Annex.Transfer
import Logs.Presence import Logs.Presence
cmd :: [Command] cmd :: Command
cmd = [withOptions moveOptions $ command "move" paramPaths seek cmd = withOptions moveOptions $ command "move" paramPaths seek
SectionCommon "move content of files to/from another repository"] SectionCommon "move content of files to/from another repository"
moveOptions :: [Option] moveOptions :: [Option]
moveOptions = fromToOptions ++ [jobsOption] ++ keyOptions ++ annexedMatchingOptions moveOptions = fromToOptions ++ [jobsOption] ++ keyOptions ++ annexedMatchingOptions

View file

@ -19,11 +19,12 @@ import Control.Concurrent
import Control.Concurrent.Async import Control.Concurrent.Async
import Control.Concurrent.STM import Control.Concurrent.STM
cmd :: [Command] cmd :: Command
cmd = [noCommit $ command "notifychanges" paramNothing seek SectionPlumbing cmd = noCommit $ command "notifychanges" paramNothing SectionPlumbing
"sends notification when git refs are changed"] "sends notification when git refs are changed"
(commandParser seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
start :: CommandStart start :: CommandStart

View file

@ -13,9 +13,9 @@ import Command
import Annex.NumCopies import Annex.NumCopies
import Types.Messages import Types.Messages
cmd :: [Command] cmd :: Command
cmd = [command "numcopies" paramNumber seek cmd = command "numcopies" paramNumber seek
SectionSetup "configure desired number of copies"] SectionSetup "configure desired number of copies"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -28,11 +28,12 @@ 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 seek SectionPlumbing cmd = command "pre-commit" paramPaths SectionPlumbing
"run by git pre-commit hook"] "run by git pre-commit hook"
(commandParser seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = lockPreCommitHook $ ifM isDirect seek ps = lockPreCommitHook $ ifM isDirect
( do ( do
-- update direct mode mappings for committed files -- update direct mode mappings for committed files

View file

@ -17,10 +17,10 @@ import qualified Git.Sha
import qualified Git.Ref import qualified Git.Ref
import qualified Git.Branch import qualified Git.Branch
cmd :: [Command] cmd :: Command
cmd = [notBareRepo $ cmd = notBareRepo $
command "proxy" ("-- git command") seek command "proxy" ("-- git command") seek
SectionPlumbing "safely bypass direct mode guard"] SectionPlumbing "safely bypass direct mode guard"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -18,10 +18,10 @@ import Logs.Location
import Utility.CopyFile import Utility.CopyFile
import qualified Remote import qualified Remote
cmd :: [Command] cmd :: Command
cmd = [notDirect $ command "rekey" cmd = notDirect $ command "rekey"
(paramOptional $ paramRepeating $ paramPair paramPath paramKey) (paramOptional $ paramRepeating $ paramPair paramPath paramKey)
seek SectionPlumbing "change keys used for files"] seek SectionPlumbing "change keys used for files"
seek :: CommandSeek seek :: CommandSeek
seek = withPairs start seek = withPairs start

View file

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

View file

@ -20,11 +20,12 @@ import qualified Types.Key
import qualified Types.Backend import qualified Types.Backend
import qualified Backend import qualified Backend
cmd :: [Command] cmd :: Command
cmd = [noCommit $ command "recvkey" paramKey seek cmd = noCommit $ command "recvkey" paramKey
SectionPlumbing "runs rsync in server mode to receive content"] SectionPlumbing "runs rsync in server mode to receive content"
(commandParser seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withKeys start seek = withKeys start
start :: Key -> CommandStart start :: Key -> CommandStart

View file

@ -15,10 +15,10 @@ import Logs.Web
import Annex.UUID import Annex.UUID
import Command.FromKey (mkKey) import Command.FromKey (mkKey)
cmd :: [Command] cmd :: Command
cmd = [notDirect $ notBareRepo $ cmd = notDirect $ notBareRepo $
command "registerurl" (paramPair paramKey paramUrl) seek command "registerurl" (paramPair paramKey paramUrl) seek
SectionPlumbing "registers an url for a key"] SectionPlumbing "registers an url for a key"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -15,8 +15,9 @@ import Types.UUID
import qualified Remote import qualified Remote
cmd :: [Command] cmd :: [Command]
cmd = [dontCheck repoExists $ cmd = dontCheck repoExists $
command "reinit" (paramUUID ++ "|" ++ paramDesc) seek SectionUtility "initialize repository, reusing old UUID"] command "reinit" (paramUUID ++ "|" ++ paramDesc) seek
SectionUtility "initialize repository, reusing old UUID"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -15,8 +15,8 @@ import qualified Command.Fsck
import qualified Backend import qualified Backend
cmd :: [Command] cmd :: [Command]
cmd = [command "reinject" (paramPair "SRC" "DEST") seek cmd = command "reinject" (paramPair "SRC" "DEST") seek
SectionUtility "sets content of annexed file"] SectionUtility "sets content of annexed file"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -11,9 +11,9 @@ import Common.Annex
import Command import Command
import RemoteDaemon.Core import RemoteDaemon.Core
cmd :: [Command] cmd :: Command
cmd = [noCommit $ command "remotedaemon" paramNothing seek SectionPlumbing cmd = noCommit $ command "remotedaemon" paramNothing seek SectionPlumbing
"detects when remotes have changed, and fetches from them"] "detects when remotes have changed, and fetches from them"
seek :: CommandSeek seek :: CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -16,9 +16,9 @@ import qualified Git.Ref
import Git.Types import Git.Types
import Annex.Version 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" paramNothing seek SectionMaintenance "recover broken git repository"
seek :: CommandSeek seek :: CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -11,7 +11,7 @@ import Command
import Logs.PreferredContent import Logs.PreferredContent
import qualified Command.Wanted import qualified Command.Wanted
cmd :: [Command] cmd :: Command
cmd = Command.Wanted.cmd' "required" "get or set required content expression" cmd = Command.Wanted.cmd' "required" "get or set required content expression"
requiredContentMapRaw requiredContentMapRaw
requiredContentSet requiredContentSet

View file

@ -14,9 +14,9 @@ import Git.Sha
import qualified Git.Branch import qualified Git.Branch
import Annex.AutoMerge import Annex.AutoMerge
cmd :: [Command] cmd :: Command
cmd = [command "resolvemerge" paramNothing seek SectionPlumbing cmd = command "resolvemerge" paramNothing seek SectionPlumbing
"resolve merge conflicts"] "resolve merge conflicts"
seek :: CommandSeek seek :: CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -13,10 +13,10 @@ import Logs.Web
import Annex.UUID import Annex.UUID
import qualified Remote import qualified Remote
cmd :: [Command] cmd :: Command
cmd = [notBareRepo $ cmd = notBareRepo $
command "rmurl" (paramPair paramFile paramUrl) seek command "rmurl" (paramPair paramFile paramUrl) seek
SectionCommon "record file is not available at url"] SectionCommon "record file is not available at url"
seek :: CommandSeek seek :: CommandSeek
seek = withPairs start seek = withPairs start

View file

@ -17,9 +17,9 @@ 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" (paramPair paramRemote (paramOptional paramExpression)) seek
SectionSetup "get or set scheduled jobs"] SectionSetup "get or set scheduled jobs"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

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

View file

@ -16,11 +16,12 @@ import Annex.Transfer
import qualified CmdLine.GitAnnexShell.Fields as Fields import qualified CmdLine.GitAnnexShell.Fields as Fields
import Utility.Metered import Utility.Metered
cmd :: [Command] cmd :: Command
cmd = [noCommit $ command "sendkey" paramKey seek cmd = noCommit $ command "sendkey" paramKey
SectionPlumbing "runs rsync in server mode to send content"] SectionPlumbing "runs rsync in server mode to send content"
(commandParser seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withKeys start seek = withKeys start
start :: Key -> CommandStart start :: Key -> CommandStart

View file

@ -13,9 +13,9 @@ import Logs.Location
import Annex.Content import Annex.Content
import Types.Key import Types.Key
cmd :: [Command] cmd :: Command
cmd = [command "setkey" (paramPair paramKey paramPath) seek cmd = command "setkey" (paramPair paramKey paramPath) seek
SectionPlumbing "sets annexed content for a key"] SectionPlumbing "sets annexed content for a key"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -13,9 +13,9 @@ import Logs.Location
import Logs.Presence.Pure 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 $ command "setpresentkey" (paramPair paramKey (paramPair paramUUID "[1|0]")) seek
SectionPlumbing "change records of where key is present"] SectionPlumbing "change records of where key is present"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -16,10 +16,10 @@ import qualified Git.LsFiles as LsFiles
import qualified Git.Ref import qualified Git.Ref
import qualified Git 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" paramPaths seek SectionCommon
"show the working tree status"] "show the working tree status"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -51,10 +51,10 @@ import Utility.Bloom
import Control.Concurrent.MVar import Control.Concurrent.MVar
import qualified Data.Map as M import qualified Data.Map as M
cmd :: [Command] cmd :: Command
cmd = [withOptions syncOptions $ cmd = withOptions syncOptions $
command "sync" (paramOptional (paramRepeating paramRemote)) command "sync" (paramOptional (paramRepeating paramRemote))
seek SectionCommon "synchronize local repository with remotes"] seek SectionCommon "synchronize local repository with remotes"
syncOptions :: [Option] syncOptions :: [Option]
syncOptions = syncOptions =

View file

@ -11,10 +11,10 @@ import Common
import Command import Command
import Messages import Messages
cmd :: [Command] cmd :: Command
cmd = [ noRepo startIO $ dontCheck repoExists $ cmd = noRepo startIO $ dontCheck repoExists $
command "test" paramNothing seek SectionTesting command "test" paramNothing seek SectionTesting
"run built-in test suite"] "run built-in test suite"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -36,10 +36,10 @@ import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.Lazy as L
import qualified Data.Map as M import qualified Data.Map as M
cmd :: [Command] cmd :: Command
cmd = [ withOptions [sizeOption] $ cmd = withOptions [sizeOption] $
command "testremote" paramRemote seek SectionTesting command "testremote" paramRemote seek SectionTesting
"test transfers to/from a remote"] "test transfers to/from a remote"
sizeOption :: Option sizeOption :: Option
sizeOption = fieldOption [] "size" paramSize "base key size (default 1MiB)" sizeOption = fieldOption [] "size" paramSize "base key size (default 1MiB)"

View file

@ -15,11 +15,12 @@ import Types.Key
import qualified CmdLine.GitAnnexShell.Fields as Fields import qualified CmdLine.GitAnnexShell.Fields as Fields
import Utility.Metered import Utility.Metered
cmd :: [Command] cmd :: Command
cmd = [noCommit $ command "transferinfo" paramKey seek SectionPlumbing cmd = noCommit $ command "transferinfo" paramKey SectionPlumbing
"updates sender on number of bytes of content received"] "updates sender on number of bytes of content received"
(commandParser seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start seek = withWords start
{- Security: {- Security:

View file

@ -15,10 +15,10 @@ import Annex.Transfer
import qualified Remote import qualified Remote
import Types.Remote import Types.Remote
cmd :: [Command] cmd :: Command
cmd = [withOptions transferKeyOptions $ cmd = withOptions transferKeyOptions $
noCommit $ command "transferkey" paramKey seek SectionPlumbing noCommit $ command "transferkey" paramKey seek SectionPlumbing
"transfers a key from or to a remote"] "transfers a key from or to a remote"
transferKeyOptions :: [Option] transferKeyOptions :: [Option]
transferKeyOptions = fileOption : fromToOptions transferKeyOptions = fileOption : fromToOptions

View file

@ -21,9 +21,9 @@ 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" paramNothing seek
SectionPlumbing "transfers keys"] SectionPlumbing "transfers keys"
seek :: CommandSeek seek :: CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -16,9 +16,9 @@ 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" (paramRepeating paramRemote) seek
SectionSetup "trust a repository"] SectionSetup "trust a repository"
seek :: CommandSeek seek :: CommandSeek
seek = trustCommand "trust" Trusted seek = trustCommand "trust" Trusted

View file

@ -22,12 +22,13 @@ import qualified Git.DiffTree as DiffTree
import Utility.CopyFile import Utility.CopyFile
import Command.PreCommit (lockPreCommitHook) import Command.PreCommit (lockPreCommitHook)
cmd :: [Command] cmd :: Command
cmd = [withOptions annexedMatchingOptions $ cmd = withOptions annexedMatchingOptions $
command "unannex" paramPaths seek SectionUtility command "unannex" paramPaths SectionUtility
"undo accidential add command"] "undo accidential add command"
(commandParser seek)
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = wrapUnannex . (withFilesInGit $ whenAnnexed start) seek = wrapUnannex . (withFilesInGit $ whenAnnexed start)
wrapUnannex :: Annex a -> Annex a wrapUnannex :: Annex a -> Annex a

View file

@ -21,10 +21,10 @@ import qualified Git.Command as Git
import qualified Git.Branch import qualified Git.Branch
import qualified Command.Sync import qualified Command.Sync
cmd :: [Command] cmd :: Command
cmd = [notBareRepo $ cmd = notBareRepo $
command "undo" paramPaths seek command "undo" paramPaths seek
SectionCommon "undo last change to a file or directory"] SectionCommon "undo last change to a file or directory"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do

View file

@ -15,9 +15,9 @@ 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" (paramPair paramRemote paramDesc) seek
SectionSetup "remove a repository from a group"] SectionSetup "remove a repository from a group"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -21,9 +21,10 @@ import Utility.FileMode
import System.IO.HVFS import System.IO.HVFS
import System.IO.HVFS.Utils import System.IO.HVFS.Utils
cmd :: [Command] cmd :: Command
cmd = [addCheck check $ command "uninit" paramPaths seek cmd = addCheck check $ command "uninit" paramPaths
SectionUtility "de-initialize git-annex and clean out repository"] SectionUtility "de-initialize git-annex and clean out repository"
(commandParser seek)
check :: Annex () check :: Annex ()
check = do check = do
@ -39,7 +40,7 @@ check = do
revhead = inRepo $ Git.Command.pipeReadStrict revhead = inRepo $ Git.Command.pipeReadStrict
[Param "rev-parse", Param "--abbrev-ref", Param "HEAD"] [Param "rev-parse", Param "--abbrev-ref", Param "HEAD"]
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
withFilesNotInGit False (whenAnnexed startCheckIncomplete) ps withFilesNotInGit False (whenAnnexed startCheckIncomplete) ps
Annex.changeState $ \s -> s { Annex.fast = True } Annex.changeState $ \s -> s { Annex.fast = True }

View file

@ -13,14 +13,15 @@ import Annex.Content
import Annex.CatFile import Annex.CatFile
import Utility.CopyFile import Utility.CopyFile
cmd :: [Command] cmd :: Command
cmd = cmd = mkcmd "unlock" "unlock files for modification"
[ c "unlock" "unlock files for modification"
, c "edit" "same as unlock" editcmd :: Command
] editcmd = mkcmd "edit" "same as unlock"
where
c n = notDirect . withOptions annexedMatchingOptions mkcmd :: String -> String -> Command
. command n paramPaths seek SectionCommon mkcmd n = notDirect . withOptions annexedMatchingOptions
. command n paramPaths seek SectionCommon
seek :: CommandSeek seek :: CommandSeek
seek = withFilesInGit $ whenAnnexed start seek = withFilesInGit $ whenAnnexed start

View file

@ -11,9 +11,9 @@ import Command
import Types.TrustLevel import Types.TrustLevel
import Command.Trust (trustCommand) import Command.Trust (trustCommand)
cmd :: [Command] cmd :: Command
cmd = [command "untrust" (paramRepeating paramRemote) seek cmd = command "untrust" (paramRepeating paramRemote) seek
SectionSetup "do not trust a repository"] SectionSetup "do not trust a repository"
seek :: CommandSeek seek :: CommandSeek
seek = trustCommand "untrust" UnTrusted seek = trustCommand "untrust" UnTrusted

View file

@ -34,10 +34,11 @@ import Git.FilePath
import Logs.View (is_branchView) import Logs.View (is_branchView)
import Annex.BloomFilter import Annex.BloomFilter
cmd :: [Command] cmd :: Command
cmd = [withOptions [unusedFromOption, refSpecOption] $ cmd = withOptions [unusedFromOption, refSpecOption] $
command "unused" paramNothing seek command "unused" paramNothing
SectionMaintenance "look for unused file content"] SectionMaintenance "look for unused file content"
(commandParser 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"
@ -45,7 +46,7 @@ unusedFromOption = fieldOption ['f'] "from" paramRemote "remote to check for unu
refSpecOption :: Option refSpecOption :: Option
refSpecOption = fieldOption [] "used-refspec" paramRefSpec "refs to consider used (default: all refs)" refSpecOption = fieldOption [] "used-refspec" paramRefSpec "refs to consider used (default: all refs)"
seek :: CommandSeek seek :: CmdParams -> CommandSeek
seek = withNothing start seek = withNothing start
{- Finds unused content in the annex. -} {- Finds unused content in the annex. -}

View file

@ -11,10 +11,10 @@ import Common.Annex
import Command import Command
import Upgrade 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" paramNothing seek
SectionMaintenance "upgrade repository layout"] SectionMaintenance "upgrade repository layout"
seek :: CommandSeek seek :: CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -12,9 +12,9 @@ import Command
import Annex.View 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 $ command "vadd" (paramRepeating "FIELD=GLOB")
seek SectionMetaData "add subdirs to current view"] seek SectionMetaData "add subdirs to current view"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -14,10 +14,10 @@ import Types.View
import Logs.View import Logs.View
import Command.View (checkoutViewBranch) import Command.View (checkoutViewBranch)
cmd :: [Command] cmd :: Command
cmd = [notBareRepo $ notDirect $ cmd = notBareRepo $ notDirect $
command "vcycle" paramNothing seek SectionMetaData command "vcycle" paramNothing seek SectionMetaData
"switch view to next layout"] "switch view to next layout"
seek :: CommandSeek seek :: CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -12,9 +12,9 @@ import Command
import Annex.View import Annex.View
import Command.View (paramView, checkoutViewBranch) 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" paramView seek SectionMetaData "filter current view"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -16,10 +16,10 @@ import Types.View
import Logs.View import Logs.View
import Command.View (checkoutViewBranch) import Command.View (checkoutViewBranch)
cmd :: [Command] cmd :: Command
cmd = [notBareRepo $ notDirect $ cmd = notBareRepo $ notDirect $
command "vpop" (paramOptional paramNumber) seek SectionMetaData command "vpop" (paramOptional paramNumber) seek SectionMetaData
"switch back to previous view"] "switch back to previous view"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -17,10 +17,10 @@ import qualified Types.Remote as R
import qualified Remote import qualified Remote
import qualified Backend 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" paramNothing seek SectionQuery "show version info"
rawOption :: Option rawOption :: Option
rawOption = flagOption [] "raw" "output only program version" rawOption = flagOption [] "raw" "output only program version"

View file

@ -29,9 +29,9 @@ import Types.StandardGroups
import Types.ScheduledActivity import Types.ScheduledActivity
import Remote import Remote
cmd :: [Command] cmd :: Command
cmd = [command "vicfg" paramNothing seek cmd = command "vicfg" paramNothing seek
SectionSetup "edit git-annex's configuration"] SectionSetup "edit git-annex's configuration"
seek :: CommandSeek seek :: CommandSeek
seek = withNothing start seek = withNothing start

View file

@ -17,9 +17,9 @@ import Types.View
import Annex.View import Annex.View
import Logs.View import Logs.View
cmd :: [Command] cmd :: Command
cmd = [notBareRepo $ notDirect $ cmd = notBareRepo $ notDirect $
command "view" paramView seek SectionMetaData "enter a view branch"] command "view" paramView seek SectionMetaData "enter a view branch"
seek :: CommandSeek seek :: CommandSeek
seek = withWords start seek = withWords start

View file

@ -17,7 +17,7 @@ import Types.StandardGroups
import qualified Data.Map as M import qualified Data.Map as M
cmd :: [Command] cmd :: Command
cmd = cmd' "wanted" "get or set preferred content expression" cmd = cmd' "wanted" "get or set preferred content expression"
preferredContentMapRaw preferredContentMapRaw
preferredContentSet preferredContentSet
@ -27,8 +27,8 @@ cmd'
-> String -> String
-> 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 pdesc seek SectionSetup desc
where where
pdesc = paramPair paramRemote (paramOptional paramExpression) pdesc = paramPair paramRemote (paramOptional paramExpression)

View file

@ -12,9 +12,9 @@ import Assistant
import Command import Command
import Utility.HumanTime 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" paramNothing seek SectionCommon "watch for changes and autocommit"
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do

View file

@ -37,10 +37,10 @@ import Control.Concurrent.STM
import Network.Socket (HostName) import Network.Socket (HostName)
import System.Environment (getArgs) 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" paramNothing seek SectionCommon "launch webapp"
listenOption :: Option listenOption :: Option
listenOption = fieldOption [] "listen" paramAddress listenOption = fieldOption [] "listen" paramAddress

Some files were not shown because too many files have changed in this diff Show more