Current status:

* building again, but several commands are commented out
* still need to implement global options, file matching options, etc
This commit is contained in:
Joey Hess 2015-07-09 19:03:21 -04:00
parent e59ba5a70b
commit 820b92abab
9 changed files with 133 additions and 100 deletions

View file

@ -15,7 +15,7 @@ import Command
import Utility.Env import Utility.Env
import Annex.Ssh import Annex.Ssh
import qualified Command.Help --import qualified Command.Help
import qualified Command.Add import qualified Command.Add
import qualified Command.Unannex import qualified Command.Unannex
import qualified Command.Drop import qualified Command.Drop
@ -25,7 +25,7 @@ import qualified Command.Get
import qualified Command.Fsck import qualified Command.Fsck
import qualified Command.LookupKey import qualified Command.LookupKey
import qualified Command.ContentLocation import qualified Command.ContentLocation
import qualified Command.ExamineKey --import qualified Command.ExamineKey
import qualified Command.FromKey import qualified Command.FromKey
import qualified Command.RegisterUrl import qualified Command.RegisterUrl
import qualified Command.SetKey import qualified Command.SetKey
@ -56,15 +56,15 @@ import qualified Command.AddUnused
import qualified Command.Unlock import qualified Command.Unlock
import qualified Command.Lock import qualified Command.Lock
import qualified Command.PreCommit import qualified Command.PreCommit
import qualified Command.Find --import qualified Command.Find
import qualified Command.FindRef --import qualified Command.FindRef
import qualified Command.Whereis --import qualified Command.Whereis
--import qualified Command.List --import qualified Command.List
import qualified Command.Log import qualified Command.Log
import qualified Command.Merge import qualified Command.Merge
import qualified Command.ResolveMerge import qualified Command.ResolveMerge
import qualified Command.Info --import qualified Command.Info
import qualified Command.Status --import qualified Command.Status
import qualified Command.Migrate import qualified Command.Migrate
import qualified Command.Uninit import qualified Command.Uninit
import qualified Command.Reinit import qualified Command.Reinit
@ -95,7 +95,7 @@ import qualified Command.Upgrade
import qualified Command.Forget import qualified Command.Forget
import qualified Command.Proxy import qualified Command.Proxy
import qualified Command.DiffDriver import qualified Command.DiffDriver
import qualified Command.Undo --import qualified Command.Undo
import qualified Command.Version import qualified Command.Version
#ifdef WITH_ASSISTANT #ifdef WITH_ASSISTANT
import qualified Command.Watch import qualified Command.Watch
@ -119,8 +119,8 @@ import System.Remote.Monitoring
cmds :: [Command] cmds :: [Command]
cmds = cmds =
[ Command.Help.cmd -- [ Command.Help.cmd
, Command.Add.cmd [ Command.Add.cmd
, Command.Get.cmd , Command.Get.cmd
, Command.Drop.cmd , Command.Drop.cmd
, Command.Move.cmd , Command.Move.cmd
@ -160,7 +160,7 @@ cmds =
-- , Command.Vicfg.cmd -- , Command.Vicfg.cmd
, Command.LookupKey.cmd , Command.LookupKey.cmd
, Command.ContentLocation.cmd , Command.ContentLocation.cmd
, Command.ExamineKey.cmd -- , Command.ExamineKey.cmd
, Command.FromKey.cmd , Command.FromKey.cmd
, Command.RegisterUrl.cmd , Command.RegisterUrl.cmd
, Command.SetKey.cmd , Command.SetKey.cmd
@ -183,15 +183,15 @@ cmds =
-- , Command.Unused.cmd -- , Command.Unused.cmd
-- , Command.DropUnused.cmd -- , Command.DropUnused.cmd
, Command.AddUnused.cmd , Command.AddUnused.cmd
, Command.Find.cmd -- , Command.Find.cmd
, Command.FindRef.cmd -- , Command.FindRef.cmd
, Command.Whereis.cmd -- , Command.Whereis.cmd
-- , Command.List.cmd -- , Command.List.cmd
, Command.Log.cmd , Command.Log.cmd
, Command.Merge.cmd , Command.Merge.cmd
, Command.ResolveMerge.cmd , Command.ResolveMerge.cmd
, Command.Info.cmd -- , Command.Info.cmd
, Command.Status.cmd -- , Command.Status.cmd
, Command.Migrate.cmd , Command.Migrate.cmd
, Command.Map.cmd , Command.Map.cmd
, Command.Direct.cmd , Command.Direct.cmd
@ -200,7 +200,7 @@ cmds =
, Command.Forget.cmd , Command.Forget.cmd
, Command.Proxy.cmd , Command.Proxy.cmd
, Command.DiffDriver.cmd , Command.DiffDriver.cmd
, Command.Undo.cmd -- , Command.Undo.cmd
, Command.Version.cmd , Command.Version.cmd
#ifdef WITH_ASSISTANT #ifdef WITH_ASSISTANT
, Command.Watch.cmd , Command.Watch.cmd

View file

@ -99,11 +99,7 @@ parseKeyOptions allowincomplete = if allowincomplete
) )
else base else base
where where
base = base = parseAllOption
flag' WantAllKeys
( long "all" <> short 'A'
<> help "operate on all versions of all files"
)
<|> flag' WantUnusedKeys <|> flag' WantUnusedKeys
( long "unused" <> short 'U' ( long "unused" <> short 'U'
<> help "operate on files found by last run of git-annex unused" <> help "operate on files found by last run of git-annex unused"
@ -113,6 +109,12 @@ parseKeyOptions allowincomplete = if allowincomplete
<> help "operate on specified key" <> help "operate on specified key"
)) ))
parseAllOption :: Parser KeyOptions
parseAllOption = flag' WantAllKeys
( long "all" <> short 'A'
<> help "operate on all versions of all files"
)
parseKey :: Monad m => String -> m Key parseKey :: Monad m => String -> m Key
parseKey = maybe (fail "invalid key") return . file2key parseKey = maybe (fail "invalid key") return . file2key
@ -121,13 +123,13 @@ annexedMatchingOptions :: [Option]
annexedMatchingOptions = concat annexedMatchingOptions = concat
[ nonWorkTreeMatchingOptions' [ nonWorkTreeMatchingOptions'
, fileMatchingOptions' , fileMatchingOptions'
, combiningOptions -- , combiningOptions
, [timeLimitOption] -- , [timeLimitOption]
] ]
-- Matching options that don't need to examine work tree files. -- Matching options that don't need to examine work tree files.
nonWorkTreeMatchingOptions :: [Option] nonWorkTreeMatchingOptions :: [Option]
nonWorkTreeMatchingOptions = nonWorkTreeMatchingOptions' ++ combiningOptions nonWorkTreeMatchingOptions = nonWorkTreeMatchingOptions' -- ++ combiningOptions
nonWorkTreeMatchingOptions' :: [Option] nonWorkTreeMatchingOptions' :: [Option]
nonWorkTreeMatchingOptions' = nonWorkTreeMatchingOptions' =
@ -153,7 +155,7 @@ nonWorkTreeMatchingOptions' =
-- Options to match files which may not yet be annexed. -- Options to match files which may not yet be annexed.
fileMatchingOptions :: [Option] fileMatchingOptions :: [Option]
fileMatchingOptions = fileMatchingOptions' ++ combiningOptions fileMatchingOptions = fileMatchingOptions' -- ++ combiningOptions
fileMatchingOptions' :: [Option] fileMatchingOptions' :: [Option]
fileMatchingOptions' = fileMatchingOptions' =
@ -167,37 +169,37 @@ fileMatchingOptions' =
"match files smaller than a size" "match files smaller than a size"
] ]
combiningOptions :: [Option] parseCombiningOptions :: Parser [GlobalSetter]
combiningOptions = parseCombiningOptions =
[ longopt "not" "negate next option" many $ longopt "not" "negate next option"
, longopt "and" "both previous and next option must match" <|> longopt "and" "both previous and next option must match"
, longopt "or" "either previous or next option must match" <|> longopt "or" "either previous or next option must match"
, shortopt "(" "open group of options" <|> shortopt '(' "open group of options"
, shortopt ")" "close group of options" <|> shortopt ')' "close group of options"
]
where where
longopt o = Option [] [o] $ NoArg $ Limit.addToken o longopt o h = globalOpt (Limit.addToken o) $ switch
shortopt o = Option o [] $ NoArg $ Limit.addToken o ( long o <> help h )
shortopt o h = globalOpt (Limit.addToken [o]) $ switch
( short o <> help h)
jsonOption :: Option parseJsonOption :: Parser GlobalSetter
jsonOption = Option ['j'] ["json"] (NoArg (Annex.setOutput JSONOutput)) parseJsonOption = globalOpt (Annex.setOutput JSONOutput) $ switch
"enable JSON output" ( long "json" <> short 'j'
<> help "enable JSON output"
)
jobsOption :: Option parseJobsOption :: Parser GlobalSetter
jobsOption = Option ['J'] ["jobs"] (ReqArg set paramNumber) parseJobsOption = globalSetter (Annex.setOutput . ParallelOutput) $
"enable concurrent jobs" option auto
where ( long "jobs" <> short 'J' <> metavar paramNumber
set s = case readish s of <> help "enable concurrent jobs"
Nothing -> error "Bad --jobs number" )
Just n -> Annex.setOutput (ParallelOutput n)
timeLimitOption :: Option parseTimeLimitOption :: Parser GlobalSetter
timeLimitOption = Option ['T'] ["time-limit"] parseTimeLimitOption = globalSetter Limit.addTimeLimit $ strOption
(ReqArg Limit.addTimeLimit paramTime) ( long "time-limit" <> short 'T' <> metavar paramTime
"stop after the specified amount of time" <> help "stop after the specified amount of time"
)
autoOption :: Option
autoOption = flagOption ['a'] "auto" "automatic mode"
parseAutoOption :: Parser Bool parseAutoOption :: Parser Bool
parseAutoOption = switch parseAutoOption = switch

View file

@ -73,9 +73,6 @@ options = commonOptions ++
unexpected expected s = error $ unexpected expected s = error $
"expected repository UUID " ++ expected ++ " but found " ++ s "expected repository UUID " ++ expected ++ " but found " ++ s
header :: String
header = "git-annex-shell [-c] command [parameters ...] [option ...]"
run :: [String] -> IO () run :: [String] -> IO ()
run [] = failure run [] = failure
-- skip leading -c options, passed by eg, ssh -- skip leading -c options, passed by eg, ssh
@ -142,14 +139,16 @@ parseFields = map (separate (== '='))
{- Only allow known fields to be set, ignore others. {- Only allow known fields to be set, ignore others.
- Make sure that field values make sense. -} - Make sure that field values make sense. -}
checkField :: (String, String) -> Bool checkField :: (String, String) -> Bool
checkField (field, value) checkField (field, val)
| field == fieldName remoteUUID = fieldCheck remoteUUID value | field == fieldName remoteUUID = fieldCheck remoteUUID val
| field == fieldName associatedFile = fieldCheck associatedFile value | field == fieldName associatedFile = fieldCheck associatedFile val
| field == fieldName direct = fieldCheck direct value | field == fieldName direct = fieldCheck direct val
| otherwise = False | otherwise = False
failure :: IO () failure :: IO ()
failure = error $ "bad parameters\n\n" ++ usage header cmds failure = error $ "bad parameters\n\n" ++ usage h cmds
where
h = "git-annex-shell [-c] command [parameters ...] [option ...]"
checkNotLimited :: IO () checkNotLimited :: IO ()
checkNotLimited = checkEnv "GIT_ANNEX_SHELL_LIMITED" checkNotLimited = checkEnv "GIT_ANNEX_SHELL_LIMITED"

View file

@ -24,7 +24,7 @@ import qualified Data.Set as S
cmd :: Command cmd :: Command
cmd = command "drop" SectionCommon cmd = command "drop" SectionCommon
"indicate content of files not currently wanted" "remove content of files from repository"
paramPaths (seek <$$> optParser) paramPaths (seek <$$> optParser)
data DropOptions = DropOptions data DropOptions = DropOptions

View file

@ -52,26 +52,32 @@ import Control.Concurrent.MVar
import qualified Data.Map as M import qualified Data.Map as M
cmd :: Command cmd :: Command
cmd = withOptions syncOptions $ cmd = command "sync" SectionCommon
command "sync" SectionCommon "synchronize local repository with remotes"
"synchronize local repository with remotes" (paramRepeating paramRemote) (seek <$$> optParser)
(paramRepeating paramRemote) (withParams seek)
syncOptions :: [Option] data SyncOptions = SyncOptions
syncOptions = { syncWith :: CmdParams
[ contentOption , contentOption :: Bool
, messageOption , messageOption :: Maybe String
, allOption , keyOptions :: Maybe KeyOptions
] }
contentOption :: Option optParser :: CmdParamsDesc -> Parser SyncOptions
contentOption = flagOption [] "content" "also transfer file contents" optParser desc = SyncOptions
<$> cmdParams desc
<*> switch
( long "content"
<> help "also transfer file contents"
)
<*> optional (strOption
( long "message" <> short 'm' <> metavar "MSG"
<> help "commit message"
))
<*> optional parseAllOption
messageOption :: Option seek :: SyncOptions -> CommandSeek
messageOption = fieldOption ['m'] "message" "MSG" "specify commit message" seek o = do
seek :: CmdParams -> CommandSeek
seek rs = do
prepMerge prepMerge
-- There may not be a branch checked out until after the commit, -- There may not be a branch checked out until after the commit,
@ -90,20 +96,20 @@ seek rs = do
) )
let withbranch a = a =<< getbranch let withbranch a = a =<< getbranch
remotes <- syncRemotes rs remotes <- syncRemotes (syncWith o)
let gitremotes = filter Remote.gitSyncableRemote remotes let gitremotes = filter Remote.gitSyncableRemote remotes
let dataremotes = filter (not . remoteAnnexIgnore . Remote.gitconfig) remotes let dataremotes = filter (not . remoteAnnexIgnore . Remote.gitconfig) remotes
-- Syncing involves many actions, any of which can independently -- Syncing involves many actions, any of which can independently
-- fail, without preventing the others from running. -- fail, without preventing the others from running.
seekActions $ return $ concat seekActions $ return $ concat
[ [ commit ] [ [ commit o ]
, [ withbranch mergeLocal ] , [ withbranch mergeLocal ]
, map (withbranch . pullRemote) gitremotes , map (withbranch . pullRemote) gitremotes
, [ mergeAnnex ] , [ mergeAnnex ]
] ]
whenM (Annex.getFlag $ optionName contentOption) $ when (contentOption o) $
whenM (seekSyncContent dataremotes) $ whenM (seekSyncContent o dataremotes) $
-- Transferring content can take a while, -- Transferring content can take a while,
-- and other changes can be pushed to the git-annex -- and other changes can be pushed to the git-annex
-- branch on the remotes in the meantime, so pull -- branch on the remotes in the meantime, so pull
@ -151,15 +157,14 @@ syncRemotes rs = ifM (Annex.getState Annex.fast) ( nub <$> pickfast , wanted )
fastest = fromMaybe [] . headMaybe . Remote.byCost fastest = fromMaybe [] . headMaybe . Remote.byCost
commit :: CommandStart commit :: SyncOptions -> CommandStart
commit = ifM (annexAutoCommit <$> Annex.getGitConfig) commit o = ifM (annexAutoCommit <$> Annex.getGitConfig)
( go ( go
, stop , stop
) )
where where
go = next $ next $ do go = next $ next $ do
commitmessage <- maybe commitMsg return commitmessage <- maybe commitMsg return (messageOption o)
=<< Annex.getField (optionName messageOption)
showStart "commit" "" showStart "commit" ""
Annex.Branch.commit "update" Annex.Branch.commit "update"
ifM isDirect ifM isDirect
@ -372,14 +377,16 @@ newer remote b = do
- -
- If any file movements were generated, returns true. - If any file movements were generated, returns true.
-} -}
seekSyncContent :: [Remote] -> Annex Bool seekSyncContent :: SyncOptions -> [Remote] -> Annex Bool
seekSyncContent rs = do seekSyncContent o rs = do
mvar <- liftIO newEmptyMVar mvar <- liftIO newEmptyMVar
bloom <- ifM (Annex.getFlag "all") bloom <- case keyOptions o of
( Just <$> genBloomFilter (seekworktree mvar []) Just WantAllKeys -> Just <$> genBloomFilter (seekworktree mvar [])
, seekworktree mvar [] (const noop) >> pure Nothing _ -> seekworktree mvar [] (const noop) >> pure Nothing
) withKeyOptions' (keyOptions o) False
withKeyOptions' False (seekkeys mvar bloom) (const noop) [] (seekkeys mvar bloom)
(const noop)
[]
liftIO $ not <$> isEmptyMVar mvar liftIO $ not <$> isEmptyMVar mvar
where where
seekworktree mvar l bloomfeeder = seekHelper LsFiles.inRepo l >>= seekworktree mvar l bloomfeeder = seekHelper LsFiles.inRepo l >>=

View file

@ -57,13 +57,13 @@ start = do
!refspec <- maybe cfgrefspec (either error id . parseRefSpec) !refspec <- maybe cfgrefspec (either error id . parseRefSpec)
<$> Annex.getField (optionName refSpecOption) <$> Annex.getField (optionName refSpecOption)
from <- Annex.getField (optionName unusedFromOption) from <- Annex.getField (optionName unusedFromOption)
let (name, action) = case from of let (name, perform) = case from of
Nothing -> (".", checkUnused refspec) Nothing -> (".", checkUnused refspec)
Just "." -> (".", checkUnused refspec) Just "." -> (".", checkUnused refspec)
Just "here" -> (".", checkUnused refspec) Just "here" -> (".", checkUnused refspec)
Just n -> (n, checkRemoteUnused n refspec) Just n -> (n, checkRemoteUnused n refspec)
showStart "unused" name showStart "unused" name
next action next perform
checkUnused :: RefSpec -> CommandPerform checkUnused :: RefSpec -> CommandPerform
checkUnused refspec = chain 0 checkUnused refspec = chain 0
@ -127,11 +127,11 @@ unusedMsg u = unusedMsg' u
["Some annexed data is no longer used by any files:"] ["Some annexed data is no longer used by any files:"]
[dropMsg Nothing] [dropMsg Nothing]
unusedMsg' :: [(Int, Key)] -> [String] -> [String] -> String unusedMsg' :: [(Int, Key)] -> [String] -> [String] -> String
unusedMsg' u header trailer = unlines $ unusedMsg' u mheader mtrailer = unlines $
header ++ mheader ++
table u ++ table u ++
["(To see where data was previously used, try: git log --stat -S'KEY')"] ++ ["(To see where data was previously used, try: git log --stat -S'KEY')"] ++
trailer mtrailer
remoteUnusedMsg :: Remote -> [(Int, Key)] -> String remoteUnusedMsg :: Remote -> [(Int, Key)] -> String
remoteUnusedMsg r u = unusedMsg' u remoteUnusedMsg r u = unusedMsg' u

View file

@ -21,6 +21,14 @@ cmd = noCommit $ withOptions (jsonOption : annexedMatchingOptions ++ keyOptions)
"lists repositories that have file content" "lists repositories that have file content"
paramPaths (withParams seek) paramPaths (withParams seek)
data WhereisOptions = WhereisOptions
{ whereisFiles :: CmdParams
, jsonOption :: GlobalSetter
, keyOptions :: Maybe KeyOptions
}
-- TODO: annexedMatchingOptions
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
m <- remoteMap id m <- remoteMap id

View file

@ -12,6 +12,8 @@ module Types.DeferredParse where
import Annex import Annex
import Common import Common
import Options.Applicative.Types
-- Some values cannot be fully parsed without performing an action. -- Some values cannot be fully parsed without performing an action.
-- The action may be expensive, so it's best to call finishParse on such a -- The action may be expensive, so it's best to call finishParse on such a
-- value before using getParsed repeatedly. -- value before using getParsed repeatedly.
@ -31,3 +33,18 @@ instance DeferredParseClass (DeferredParse a) where
instance DeferredParseClass (Maybe (DeferredParse a)) where instance DeferredParseClass (Maybe (DeferredParse a)) where
finishParse Nothing = pure Nothing finishParse Nothing = pure Nothing
finishParse (Just v) = Just <$> finishParse v finishParse (Just v) = Just <$> finishParse v
instance DeferredParseClass [DeferredParse a] where
finishParse v = mapM finishParse v
-- Use when the Annex action modifies Annex state.
type GlobalSetter = DeferredParse ()
globalOpt :: Annex () -> Parser Bool -> Parser GlobalSetter
globalOpt setter parser = go <$> parser
where
go False = ReadyParse ()
go True = DeferredParse setter
globalSetter :: (v -> Annex ()) -> Parser v -> Parser GlobalSetter
globalSetter setter parser = DeferredParse . setter <$> parser

View file

@ -1,6 +1,6 @@
# NAME # NAME
git-annex drop - indicate content of files not currently wanted git-annex drop - remove content of files from repository
# SYNOPSIS # SYNOPSIS