arrange for regional output manager to run when -J is enabled
Commands that want to use it have to run their seek action inside allowConcurrentOutput. Which seems reasonable; perhaps some future command will want to support the -J flag but not use regions. The region state moved from Annex to MessageState. This makes sense organizationally, and note that some uses of onLocal use a different Annex state, but pass the MessageState into it, which is what is needed.
This commit is contained in:
parent
a4dd8503b8
commit
c0c595345c
12 changed files with 58 additions and 50 deletions
13
Annex.hs
13
Annex.hs
|
@ -65,9 +65,6 @@ import Utility.Quvi (QuviVersion)
|
||||||
#endif
|
#endif
|
||||||
import Utility.InodeCache
|
import Utility.InodeCache
|
||||||
import Utility.Url
|
import Utility.Url
|
||||||
#ifdef WITH_CONCURRENTOUTPUT
|
|
||||||
import System.Console.Regions (ConsoleRegion)
|
|
||||||
#endif
|
|
||||||
|
|
||||||
import "mtl" Control.Monad.Reader
|
import "mtl" Control.Monad.Reader
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
|
@ -136,10 +133,7 @@ data AnnexState = AnnexState
|
||||||
, existinghooks :: M.Map Git.Hook.Hook Bool
|
, existinghooks :: M.Map Git.Hook.Hook Bool
|
||||||
, desktopnotify :: DesktopNotify
|
, desktopnotify :: DesktopNotify
|
||||||
, workers :: [Either AnnexState (Async AnnexState)]
|
, workers :: [Either AnnexState (Async AnnexState)]
|
||||||
#ifdef WITH_CONCURRENTOUTPUT
|
, concurrentjobs :: Maybe Int
|
||||||
, consoleregion :: Maybe ConsoleRegion
|
|
||||||
, consoleregionerrflag :: Bool
|
|
||||||
#endif
|
|
||||||
}
|
}
|
||||||
|
|
||||||
newState :: GitConfig -> Git.Repo -> AnnexState
|
newState :: GitConfig -> Git.Repo -> AnnexState
|
||||||
|
@ -184,10 +178,7 @@ newState c r = AnnexState
|
||||||
, existinghooks = M.empty
|
, existinghooks = M.empty
|
||||||
, desktopnotify = mempty
|
, desktopnotify = mempty
|
||||||
, workers = []
|
, workers = []
|
||||||
#ifdef WITH_CONCURRENTOUTPUT
|
, concurrentjobs = Nothing
|
||||||
, consoleregion = Nothing
|
|
||||||
, consoleregionerrflag = True
|
|
||||||
#endif
|
|
||||||
}
|
}
|
||||||
|
|
||||||
{- Makes an Annex state object for the specified git repo.
|
{- Makes an Annex state object for the specified git repo.
|
||||||
|
|
|
@ -24,7 +24,6 @@ import Annex.Action
|
||||||
import Annex.Environment
|
import Annex.Environment
|
||||||
import Command
|
import Command
|
||||||
import Types.Messages
|
import Types.Messages
|
||||||
import Messages.Internal
|
|
||||||
|
|
||||||
{- Runs the passed command line. -}
|
{- Runs the passed command line. -}
|
||||||
dispatch :: Bool -> CmdParams -> [Command] -> [GlobalOption] -> [(String, String)] -> IO Git.Repo -> String -> String -> IO ()
|
dispatch :: Bool -> CmdParams -> [Command] -> [GlobalOption] -> [(String, String)] -> IO Git.Repo -> String -> String -> IO ()
|
||||||
|
@ -46,9 +45,8 @@ dispatch fuzzyok allargs allcmds globaloptions fields getgitrepo progname progde
|
||||||
whenM (annexDebug <$> Annex.getGitConfig) $
|
whenM (annexDebug <$> Annex.getGitConfig) $
|
||||||
liftIO enableDebugOutput
|
liftIO enableDebugOutput
|
||||||
startup
|
startup
|
||||||
withConcurrentOutput $
|
performCommandAction cmd seek $
|
||||||
performCommandAction cmd seek $
|
shutdown $ cmdnocommit cmd
|
||||||
shutdown $ cmdnocommit cmd
|
|
||||||
go (Left norepo) = do
|
go (Left norepo) = do
|
||||||
let ingitrepo = \a -> a =<< Git.Config.global
|
let ingitrepo = \a -> a =<< Git.Config.global
|
||||||
-- Parse command line with full cmdparser first,
|
-- Parse command line with full cmdparser first,
|
||||||
|
|
|
@ -56,7 +56,8 @@ commandAction a = withOutputType go
|
||||||
else do
|
else do
|
||||||
l <- liftIO $ drainTo (n-1) ws
|
l <- liftIO $ drainTo (n-1) ws
|
||||||
findFreeSlot l
|
findFreeSlot l
|
||||||
w <- liftIO $ async $ snd <$> Annex.run st run
|
w <- liftIO $ async
|
||||||
|
$ snd <$> Annex.run st (inOwnConsoleRegion run)
|
||||||
Annex.changeState $ \s -> s { Annex.workers = Right w:ws' }
|
Annex.changeState $ \s -> s { Annex.workers = Right w:ws' }
|
||||||
go _ = run
|
go _ = run
|
||||||
run = void $ includeCommandAction a
|
run = void $ includeCommandAction a
|
||||||
|
|
|
@ -282,13 +282,17 @@ jsonOption = globalFlag (Annex.setOutput JSONOutput)
|
||||||
<> hidden
|
<> hidden
|
||||||
)
|
)
|
||||||
|
|
||||||
|
-- Note that a command that adds this option should wrap its seek
|
||||||
|
-- action in `allowConcurrentOutput`.
|
||||||
jobsOption :: GlobalOption
|
jobsOption :: GlobalOption
|
||||||
jobsOption = globalSetter (Annex.setOutput . ConcurrentOutput) $
|
jobsOption = globalSetter set $
|
||||||
option auto
|
option auto
|
||||||
( long "jobs" <> short 'J' <> metavar paramNumber
|
( long "jobs" <> short 'J' <> metavar paramNumber
|
||||||
<> help "enable concurrent jobs"
|
<> help "enable concurrent jobs"
|
||||||
<> hidden
|
<> hidden
|
||||||
)
|
)
|
||||||
|
where
|
||||||
|
set n = Annex.changeState $ \s -> s { Annex.concurrentjobs = Just n }
|
||||||
|
|
||||||
timeLimitOption :: GlobalOption
|
timeLimitOption :: GlobalOption
|
||||||
timeLimitOption = globalSetter Limit.addTimeLimit $ strOption
|
timeLimitOption = globalSetter Limit.addTimeLimit $ strOption
|
||||||
|
|
|
@ -19,6 +19,7 @@ module Command (
|
||||||
whenAnnexed,
|
whenAnnexed,
|
||||||
ifAnnexed,
|
ifAnnexed,
|
||||||
isBareRepo,
|
isBareRepo,
|
||||||
|
allowConcurrentOutput,
|
||||||
module ReExported
|
module ReExported
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
@ -36,6 +37,7 @@ import CmdLine.Option as ReExported
|
||||||
import CmdLine.GlobalSetter as ReExported
|
import CmdLine.GlobalSetter as ReExported
|
||||||
import CmdLine.GitAnnex.Options as ReExported
|
import CmdLine.GitAnnex.Options as ReExported
|
||||||
import Options.Applicative as ReExported hiding (command)
|
import Options.Applicative as ReExported hiding (command)
|
||||||
|
import Messages.Internal (allowConcurrentOutput)
|
||||||
|
|
||||||
import qualified Options.Applicative as O
|
import qualified Options.Applicative as O
|
||||||
|
|
||||||
|
|
|
@ -37,7 +37,7 @@ optParser desc = GetOptions
|
||||||
<*> optional (parseKeyOptions True)
|
<*> optional (parseKeyOptions True)
|
||||||
|
|
||||||
seek :: GetOptions -> CommandSeek
|
seek :: GetOptions -> CommandSeek
|
||||||
seek o = do
|
seek o = allowConcurrentOutput $ do
|
||||||
from <- maybe (pure Nothing) (Just <$$> getParsed) (getFrom o)
|
from <- maybe (pure Nothing) (Just <$$> getParsed) (getFrom o)
|
||||||
withKeyOptions (keyOptions o) (autoMode o)
|
withKeyOptions (keyOptions o) (autoMode o)
|
||||||
(startKeys from)
|
(startKeys from)
|
||||||
|
|
|
@ -41,10 +41,11 @@ instance DeferredParseClass MirrorOptions where
|
||||||
<*> pure (keyOptions v)
|
<*> pure (keyOptions v)
|
||||||
|
|
||||||
seek :: MirrorOptions -> CommandSeek
|
seek :: MirrorOptions -> CommandSeek
|
||||||
seek o = withKeyOptions (keyOptions o) False
|
seek o = allowConcurrentOutput $
|
||||||
(startKey o Nothing)
|
withKeyOptions (keyOptions o) False
|
||||||
(withFilesInGit $ whenAnnexed $ start o)
|
(startKey o Nothing)
|
||||||
(mirrorFiles o)
|
(withFilesInGit $ whenAnnexed $ start o)
|
||||||
|
(mirrorFiles o)
|
||||||
|
|
||||||
start :: MirrorOptions -> FilePath -> Key -> CommandStart
|
start :: MirrorOptions -> FilePath -> Key -> CommandStart
|
||||||
start o file = startKey o (Just file)
|
start o file = startKey o (Just file)
|
||||||
|
|
|
@ -45,10 +45,11 @@ instance DeferredParseClass MoveOptions where
|
||||||
<*> pure (keyOptions v)
|
<*> pure (keyOptions v)
|
||||||
|
|
||||||
seek :: MoveOptions -> CommandSeek
|
seek :: MoveOptions -> CommandSeek
|
||||||
seek o = withKeyOptions (keyOptions o) False
|
seek o = allowConcurrentOutput $
|
||||||
(startKey o True)
|
withKeyOptions (keyOptions o) False
|
||||||
(withFilesInGit $ whenAnnexed $ start o True)
|
(startKey o True)
|
||||||
(moveFiles o)
|
(withFilesInGit $ whenAnnexed $ start o True)
|
||||||
|
(moveFiles o)
|
||||||
|
|
||||||
start :: MoveOptions -> Bool -> FilePath -> Key -> CommandStart
|
start :: MoveOptions -> Bool -> FilePath -> Key -> CommandStart
|
||||||
start o move = start' o move . Just
|
start o move = start' o move . Just
|
||||||
|
|
|
@ -93,7 +93,7 @@ optParser desc = SyncOptions
|
||||||
<*> optional parseAllOption
|
<*> optional parseAllOption
|
||||||
|
|
||||||
seek :: SyncOptions -> CommandSeek
|
seek :: SyncOptions -> CommandSeek
|
||||||
seek o = do
|
seek o = allowConcurrentOutput $ 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,
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||||
|
|
||||||
{- git-annex output messages, including concurrent output
|
{- git-annex output messages, including concurrent output to display regions
|
||||||
-
|
-
|
||||||
- Copyright 2010-2015 Joey Hess <id@joeyh.name>
|
- Copyright 2010-2015 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
|
@ -58,35 +58,38 @@ flushed a = a >> hFlush stdout
|
||||||
-}
|
-}
|
||||||
concurrentMessage :: Bool -> String -> Annex () -> Annex ()
|
concurrentMessage :: Bool -> String -> Annex () -> Annex ()
|
||||||
#ifdef WITH_CONCURRENTOUTPUT
|
#ifdef WITH_CONCURRENTOUTPUT
|
||||||
concurrentMessage iserror msg _ = go =<< Annex.getState Annex.consoleregion
|
concurrentMessage iserror msg _ = go =<< consoleRegion <$> Annex.getState Annex.output
|
||||||
where
|
where
|
||||||
go Nothing
|
go Nothing
|
||||||
| iserror = liftIO $ Console.errorConcurrent msg
|
| iserror = liftIO $ Console.errorConcurrent msg
|
||||||
| otherwise = liftIO $ Console.outputConcurrent msg
|
| otherwise = do
|
||||||
|
liftIO $ Console.outputConcurrent ("REGION MESSAGE NO REGION" ++ show msg)
|
||||||
|
liftIO $ Console.outputConcurrent msg
|
||||||
go (Just r) = do
|
go (Just r) = do
|
||||||
|
liftIO $ Console.outputConcurrent ("REGION MESSAGE " ++ show msg)
|
||||||
-- Can't display the error to stdout while
|
-- Can't display the error to stdout while
|
||||||
-- console regions are in use, so set the errflag
|
-- console regions are in use, so set the errflag
|
||||||
-- to get it to display to stderr later.
|
-- to get it to display to stderr later.
|
||||||
when iserror $
|
when iserror $ do
|
||||||
Annex.changeState $ \s -> s { Annex.consoleregionerrflag = True }
|
Annex.changeState $ \s ->
|
||||||
|
s { Annex.output = (Annex.output s) { consoleRegionErrFlag = True } }
|
||||||
liftIO $ Regions.appendConsoleRegion r msg
|
liftIO $ Regions.appendConsoleRegion r msg
|
||||||
#else
|
#else
|
||||||
concurrentMessage _ _ fallback = fallback
|
concurrentMessage _ _ fallback = fallback
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
{- Enable concurrent output when that has been requested.
|
{- Do concurrent output when that has been requested. -}
|
||||||
-
|
allowConcurrentOutput :: Annex a -> Annex a
|
||||||
- This should only be run once per git-annex lifetime, with
|
|
||||||
- everything that might generate messages run inside it.
|
|
||||||
-}
|
|
||||||
withConcurrentOutput :: Annex a -> Annex a
|
|
||||||
#ifdef WITH_CONCURRENTOUTPUT
|
#ifdef WITH_CONCURRENTOUTPUT
|
||||||
withConcurrentOutput a = withOutputType go
|
allowConcurrentOutput a = go =<< Annex.getState Annex.concurrentjobs
|
||||||
where
|
where
|
||||||
go (ConcurrentOutput _) = Console.withConcurrentOutput a
|
go (Just n) = Regions.displayConsoleRegions $ bracket_
|
||||||
go _ = a
|
(Annex.setOutput (ConcurrentOutput n))
|
||||||
|
(Annex.setOutput NormalOutput)
|
||||||
|
a
|
||||||
|
go Nothing = a
|
||||||
#else
|
#else
|
||||||
withConcurrentOutput = id
|
allowConcurrentOutput = id
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
{- Runs an action in its own dedicated region of the console.
|
{- Runs an action in its own dedicated region of the console.
|
||||||
|
@ -103,11 +106,12 @@ inOwnConsoleRegion a = Regions.withConsoleRegion Regions.Linear $ \r -> do
|
||||||
setregion (Just r)
|
setregion (Just r)
|
||||||
a `finally` removeregion r
|
a `finally` removeregion r
|
||||||
where
|
where
|
||||||
setregion v = Annex.changeState $ \s -> s { Annex.consoleregion = v }
|
setregion r = Annex.changeState $ \s -> s { Annex.output = (Annex.output s) { consoleRegion = r } }
|
||||||
removeregion r = do
|
removeregion r = do
|
||||||
errflag <- Annex.getState Annex.consoleregionerrflag
|
errflag <- consoleRegionErrFlag <$> Annex.getState Annex.output
|
||||||
let h = if errflag then Console.StdErr else Console.StdOut
|
let h = if errflag then Console.StdErr else Console.StdOut
|
||||||
Annex.changeState $ \s -> s { Annex.consoleregionerrflag = False }
|
Annex.changeState $ \s ->
|
||||||
|
s { Annex.output = (Annex.output s) { consoleRegionErrFlag = False } }
|
||||||
setregion Nothing
|
setregion Nothing
|
||||||
liftIO $ atomically $ do
|
liftIO $ atomically $ do
|
||||||
t <- Regions.getConsoleRegion r
|
t <- Regions.getConsoleRegion r
|
||||||
|
|
|
@ -65,10 +65,7 @@ metered combinemeterupdate key af a = case keySize key of
|
||||||
return r
|
return r
|
||||||
#else
|
#else
|
||||||
-- Old progress bar code, not suitable for concurrent output.
|
-- Old progress bar code, not suitable for concurrent output.
|
||||||
go _ (ConcurrentOutput _) = do
|
go _ (ConcurrentOutput _) = nometer
|
||||||
r <- nometer
|
|
||||||
liftIO $ putStrLn $ fromMaybe (key2file key) af
|
|
||||||
return r
|
|
||||||
go size NormalOutput = do
|
go size NormalOutput = do
|
||||||
showOutput
|
showOutput
|
||||||
progress <- liftIO $ newProgress "" size
|
progress <- liftIO $ newProgress "" size
|
||||||
|
|
|
@ -5,11 +5,18 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
module Types.Messages where
|
module Types.Messages where
|
||||||
|
|
||||||
import Data.Default
|
import Data.Default
|
||||||
|
|
||||||
|
#ifdef WITH_CONCURRENTOUTPUT
|
||||||
|
import System.Console.Regions (ConsoleRegion)
|
||||||
|
#endif
|
||||||
|
|
||||||
data OutputType = NormalOutput | QuietOutput | ConcurrentOutput Int | JSONOutput
|
data OutputType = NormalOutput | QuietOutput | ConcurrentOutput Int | JSONOutput
|
||||||
|
deriving (Show)
|
||||||
|
|
||||||
data SideActionBlock = NoBlock | StartBlock | InBlock
|
data SideActionBlock = NoBlock | StartBlock | InBlock
|
||||||
deriving (Eq)
|
deriving (Eq)
|
||||||
|
@ -17,8 +24,10 @@ data SideActionBlock = NoBlock | StartBlock | InBlock
|
||||||
data MessageState = MessageState
|
data MessageState = MessageState
|
||||||
{ outputType :: OutputType
|
{ outputType :: OutputType
|
||||||
, sideActionBlock :: SideActionBlock
|
, sideActionBlock :: SideActionBlock
|
||||||
|
, consoleRegion :: Maybe ConsoleRegion
|
||||||
|
, consoleRegionErrFlag :: Bool
|
||||||
}
|
}
|
||||||
|
|
||||||
instance Default MessageState
|
instance Default MessageState
|
||||||
where
|
where
|
||||||
def = MessageState NormalOutput NoBlock
|
def = MessageState NormalOutput NoBlock Nothing False
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue