finish CommandStart transition

The hoped for optimisation of CommandStart with -J did not materialize.
In fact, not runnign CommandStart in parallel is slower than -J3.
So, CommandStart are still run in parallel.

(The actual bad performance I've been seeing with -J in my big repo
has to do with building the remoteList.)

But, this is still progress toward making -J faster, because it gets rid
of the onlyActionOn roadblock in the way of making CommandCleanup jobs
run separate from CommandPerform jobs.

Added OnlyActionOn constructor for ActionItem which fixes the
onlyActionOn breakage in the last commit.

Made CustomOutput include an ActionItem, so even things using it can
specify OnlyActionOn.

In Command.Move and Command.Sync, there were CommandStarts that used
includeCommandAction, so output messages, which is no longer allowed.
Fixed by using startingCustomOutput, but that's still not quite right,
since it prevents message display for the includeCommandAction run
inside it too.
This commit is contained in:
Joey Hess 2019-06-12 09:23:26 -04:00
parent 436f107715
commit 8e5ea28c26
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
26 changed files with 142 additions and 97 deletions

View file

@ -59,7 +59,7 @@ seek (UnsetConfig name) = commandAction $
unsetConfig (ConfigKey name)
next $ return True
seek (GetConfig name) = commandAction $
startingCustomOutput $ do
startingCustomOutput (ActionItemOther Nothing) $ do
getGlobalConfig name >>= \case
Nothing -> return ()
Just v -> liftIO $ putStrLn v

View file

@ -91,12 +91,12 @@ startKeys o (key, ai) = start' o key (AssociatedFile Nothing) ai
startLocal :: AssociatedFile -> ActionItem -> NumCopies -> Key -> [VerifiedCopy] -> CommandStart
startLocal afile ai numcopies key preverified =
stopUnless (inAnnex key) $
starting "drop" ai $
starting "drop" (OnlyActionOn key ai) $
performLocal key afile numcopies preverified
startRemote :: AssociatedFile -> ActionItem -> NumCopies -> Key -> Remote -> CommandStart
startRemote afile ai numcopies key remote =
starting ("drop " ++ Remote.name remote) ai $
starting ("drop " ++ Remote.name remote) (OnlyActionOn key ai) $
performRemote key afile numcopies remote
performLocal :: Key -> AssociatedFile -> NumCopies -> [VerifiedCopy] -> CommandPerform

View file

@ -66,7 +66,7 @@ seek o = case batchOption o of
start :: FindOptions -> FilePath -> Key -> CommandStart
start o file key =
stopUnless (limited <||> inAnnex key) $
startingCustomOutput $ do
startingCustomOutput key $ do
showFormatted (formatOption o) file $ ("file", file) : keyVars key
next $ return True

View file

@ -71,7 +71,7 @@ start' expensivecheck from key afile ai =
stopUnless (Command.Move.fromOk src key) $
go $ Command.Move.fromPerform src Command.Move.RemoveNever key afile
where
go = starting "get" ai
go = starting "get" (OnlyActionOn key ai)
perform :: Key -> AssociatedFile -> CommandPerform
perform key afile = stopUnless (getKey key afile) $

View file

@ -28,7 +28,7 @@ start (name:g:[]) = do
setGroup u (toGroup g)
start (name:[]) = do
u <- Remote.nameToUUID name
startingCustomOutput $ do
startingCustomOutput (ActionItemOther Nothing) $ do
liftIO . putStrLn . unwords . map fmt . S.toList
=<< lookupGroups u
next $ return True

View file

@ -22,7 +22,7 @@ seek :: CmdParams -> CommandSeek
seek = withWords (commandAction . start)
start :: [String] -> CommandStart
start (g:[]) = startingCustomOutput $
start (g:[]) = startingCustomOutput (ActionItemOther Nothing) $
performGet groupPreferredContentMapRaw (toGroup g)
start (g:expr:[]) = startingUsualMessages "groupwanted" (ActionItemOther (Just g)) $
performSet groupPreferredContentSet expr (toGroup g)

View file

@ -279,7 +279,8 @@ seekRemote remote branch msubdir = do
, ". Re-run command to resume import."
]
Just imported -> void $
includeCommandAction $ commitimport imported
includeCommandAction $
commitimport imported
where
importmessage = "import from " ++ Remote.name remote

View file

@ -48,7 +48,7 @@ start s _file k
| otherwise = stop
start' :: Key -> CommandStart
start' k = startingCustomOutput $ do
start' k = startingCustomOutput k $ do
tmpf <- fromRepo $ gitAnnexTmpObjectLocation k
whenM (liftIO $ doesFileExist tmpf) $
liftIO $ putStrLn tmpf

View file

@ -99,7 +99,7 @@ start c o file k = startKeys c o (k, mkActionItem (k, afile))
startKeys :: VectorClock -> MetaDataOptions -> (Key, ActionItem) -> CommandStart
startKeys c o (k, ai) = case getSet o of
Get f -> startingCustomOutput $ do
Get f -> startingCustomOutput k $ do
l <- S.toList . currentMetaDataValues f <$> getCurrentMetaData k
liftIO $ forM_ l $
B8.putStrLn . fromMetaValue

View file

@ -108,8 +108,9 @@ toStart' dest removewhen afile key ai = do
)
else go False (Remote.hasKey dest key)
where
go fastcheck isthere = starting (describeMoveAction removewhen) ai $
toPerform dest removewhen key afile fastcheck =<< isthere
go fastcheck isthere =
starting (describeMoveAction removewhen) (OnlyActionOn key ai) $
toPerform dest removewhen key afile fastcheck =<< isthere
expectedPresent :: Remote -> Key -> Annex Bool
expectedPresent dest key = do
@ -182,7 +183,7 @@ fromStart removewhen afile key ai src = case removewhen of
RemoveSafe -> go
where
go = stopUnless (fromOk src key) $
starting (describeMoveAction removewhen) ai $
starting (describeMoveAction removewhen) (OnlyActionOn key ai) $
fromPerform src removewhen key afile
fromOk :: Remote -> Key -> Annex Bool
@ -246,13 +247,13 @@ toHereStart removewhen afile key ai = case removewhen of
RemoveNever -> stopUnless (not <$> inAnnex key) go
RemoveSafe -> go
where
go = do
go = startingCustomOutput (OnlyActionOn key ai) $ do
rs <- Remote.keyPossibilities key
forM_ rs $ \r ->
includeCommandAction $
starting (describeMoveAction removewhen) ai $
fromPerform r removewhen key afile
stop
next $ return True
{- The goal of this command is to allow the user maximum freedom to move
- files as they like, while avoiding making bad situations any worse

View file

@ -33,7 +33,7 @@ start [s] = case readish s of
start _ = giveup "Specify a single number."
startGet :: CommandStart
startGet = startingCustomOutput $ next $ do
startGet = startingCustomOutput (ActionItemOther Nothing) $ next $ do
v <- getGlobalNumCopies
case v of
Just n -> liftIO $ putStrLn $ show $ fromNumCopies n

View file

@ -27,7 +27,7 @@ seek [u] = commandAction $ start $ toUUID u
seek _ = giveup "missing UUID parameter"
start :: UUID -> CommandStart
start theiruuid = startingCustomOutput $ do
start theiruuid = startingCustomOutput (ActionItemOther Nothing) $ do
servermode <- liftIO $ do
ro <- Checks.checkEnvSet Checks.readOnlyEnv
ao <- Checks.checkEnvSet Checks.appendOnlyEnv

View file

@ -84,13 +84,14 @@ seek ps = lockPreCommitHook $ ifM isDirect
startInjectUnlocked :: FilePath -> CommandStart
startInjectUnlocked f = startingCustomOutput $ do
startInjectUnlocked f = startingCustomOutput (ActionItemOther Nothing) $ do
unlessM (callCommandAction $ Command.Add.start f) $
error $ "failed to add " ++ f ++ "; canceling commit"
next $ return True
startDirect :: [String] -> CommandStart
startDirect _ = startingCustomOutput $ next preCommitDirect
startDirect _ = startingCustomOutput (ActionItemOther Nothing) $
next preCommitDirect
addViewMetaData :: View -> ViewedFile -> Key -> CommandStart
addViewMetaData v f k = starting "metadata" (mkActionItem (k, f)) $

View file

@ -27,7 +27,7 @@ start = parse
where
parse (name:[]) = do
u <- Remote.nameToUUID name
startingCustomOutput $
startingCustomOutput (ActionItemOther Nothing) $
performGet u
parse (name:expr:[]) = do
u <- Remote.nameToUUID name

View file

@ -626,10 +626,14 @@ seekSyncContent o rs currbranch = do
gokey mvar bloom (k, _) = go (Left bloom) mvar (AssociatedFile Nothing) k
go ebloom mvar af k = commandAction $ do
whenM (syncFile ebloom rs af k) $
void $ liftIO $ tryPutMVar mvar ()
return Nothing
go ebloom mvar af k = do
-- Run syncFile as a command action so file transfers run
-- concurrently.
let ai = OnlyActionOn k (ActionItemKey k)
commandAction $ startingCustomOutput ai $ do
whenM (syncFile ebloom rs af k) $
void $ liftIO $ tryPutMVar mvar ()
next $ return True
{- If it's preferred content, and we don't have it, get it from one of the
- listed remotes (preferring the cheaper earlier ones).
@ -645,7 +649,7 @@ seekSyncContent o rs currbranch = do
- Returns True if any file transfers were made.
-}
syncFile :: Either (Maybe (Bloom Key)) (Key -> Annex ()) -> [Remote] -> AssociatedFile -> Key -> Annex Bool
syncFile ebloom rs af k = onlyActionOn' k $ do
syncFile ebloom rs af k = do
inhere <- inAnnex k
locs <- map Remote.uuid <$> Remote.keyPossibilities k
let (have, lack) = partition (\r -> Remote.uuid r `elem` locs) rs

View file

@ -45,7 +45,7 @@ seek :: TransferKeyOptions -> CommandSeek
seek o = withKeys (commandAction . start o) (keyOptions o)
start :: TransferKeyOptions -> Key -> CommandStart
start o key = startingCustomOutput $ case fromToOptions o of
start o key = startingCustomOutput key $ case fromToOptions o of
ToRemote dest -> toPerform key (fileOption o) =<< getParsed dest
FromRemote src -> fromPerform key (fileOption o) =<< getParsed src

View file

@ -34,7 +34,7 @@ cmd' name desc getter setter = noMessages $
start (rname:[]) = do
u <- Remote.nameToUUID rname
startingCustomOutput $
startingCustomOutput (ActionItemOther Nothing) $
performGet getter u
start (rname:expr:[]) = do
u <- Remote.nameToUUID rname