add regions to concurrent output
still no progress displays when getting files etc, but a big improvement
This commit is contained in:
parent
4fd03ccd7b
commit
a4dd8503b8
6 changed files with 101 additions and 55 deletions
11
Annex.hs
11
Annex.hs
|
@ -65,6 +65,9 @@ import Utility.Quvi (QuviVersion)
|
|||
#endif
|
||||
import Utility.InodeCache
|
||||
import Utility.Url
|
||||
#ifdef WITH_CONCURRENTOUTPUT
|
||||
import System.Console.Regions (ConsoleRegion)
|
||||
#endif
|
||||
|
||||
import "mtl" Control.Monad.Reader
|
||||
import Control.Concurrent
|
||||
|
@ -133,6 +136,10 @@ data AnnexState = AnnexState
|
|||
, existinghooks :: M.Map Git.Hook.Hook Bool
|
||||
, desktopnotify :: DesktopNotify
|
||||
, workers :: [Either AnnexState (Async AnnexState)]
|
||||
#ifdef WITH_CONCURRENTOUTPUT
|
||||
, consoleregion :: Maybe ConsoleRegion
|
||||
, consoleregionerrflag :: Bool
|
||||
#endif
|
||||
}
|
||||
|
||||
newState :: GitConfig -> Git.Repo -> AnnexState
|
||||
|
@ -177,6 +184,10 @@ newState c r = AnnexState
|
|||
, existinghooks = M.empty
|
||||
, desktopnotify = mempty
|
||||
, workers = []
|
||||
#ifdef WITH_CONCURRENTOUTPUT
|
||||
, consoleregion = Nothing
|
||||
, consoleregionerrflag = True
|
||||
#endif
|
||||
}
|
||||
|
||||
{- Makes an Annex state object for the specified git repo.
|
||||
|
|
|
@ -51,7 +51,7 @@ dupState = do
|
|||
}
|
||||
|
||||
{- Merges the passed AnnexState into the current Annex state.
|
||||
- Also shuts closes various handles in it. -}
|
||||
- Also closes various handles in it. -}
|
||||
mergeState :: AnnexState -> Annex ()
|
||||
mergeState st = do
|
||||
st' <- liftIO $ snd <$> run st closehandles
|
||||
|
|
|
@ -24,7 +24,7 @@ import Annex.Action
|
|||
import Annex.Environment
|
||||
import Command
|
||||
import Types.Messages
|
||||
import Messages.Concurrent
|
||||
import Messages.Internal
|
||||
|
||||
{- Runs the passed command line. -}
|
||||
dispatch :: Bool -> CmdParams -> [Command] -> [GlobalOption] -> [(String, String)] -> IO Git.Repo -> String -> String -> IO ()
|
||||
|
|
|
@ -1,33 +0,0 @@
|
|||
{- git-annex concurrent output
|
||||
-
|
||||
- Copyright 2015 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
|
||||
module Messages.Concurrent where
|
||||
|
||||
import Common.Annex
|
||||
import Messages.Internal
|
||||
import Types.Messages
|
||||
|
||||
#ifdef WITH_CONCURRENTOUTPUT
|
||||
import qualified System.Console.Concurrent as Console
|
||||
#endif
|
||||
|
||||
{- Enable concurrent output when that has been requested.
|
||||
-
|
||||
- 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
|
||||
withConcurrentOutput a = withOutputType go
|
||||
where
|
||||
go (ConcurrentOutput _) = Console.withConcurrentOutput a
|
||||
go _ = a
|
||||
#else
|
||||
withConcurrentOutput = id
|
||||
#endif
|
|
@ -1,6 +1,8 @@
|
|||
{- git-annex output messages
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||
|
||||
{- git-annex output messages, including concurrent output
|
||||
-
|
||||
- Copyright 2010-2014 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2010-2015 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
@ -10,37 +12,32 @@
|
|||
module Messages.Internal where
|
||||
|
||||
import Common
|
||||
import Types
|
||||
import Annex
|
||||
import Types.Messages
|
||||
import qualified Annex
|
||||
|
||||
#ifdef WITH_CONCURRENTOUTPUT
|
||||
import System.Console.Concurrent
|
||||
import qualified System.Console.Concurrent as Console
|
||||
import qualified System.Console.Regions as Regions
|
||||
import Data.String
|
||||
import Control.Concurrent.STM
|
||||
#endif
|
||||
|
||||
withOutputType :: (OutputType -> Annex a) -> Annex a
|
||||
withOutputType a = outputType <$> Annex.getState Annex.output >>= a
|
||||
|
||||
outputMessage :: IO () -> String -> Annex ()
|
||||
outputMessage json s = withOutputType go
|
||||
where
|
||||
go NormalOutput = liftIO $
|
||||
flushed $ putStr s
|
||||
go QuietOutput = q
|
||||
go (ConcurrentOutput _) = liftIO $
|
||||
#ifdef WITH_CONCURRENTOUTPUT
|
||||
outputConcurrent s
|
||||
#else
|
||||
q
|
||||
#endif
|
||||
go (ConcurrentOutput _) = concurrentMessage False s q
|
||||
go JSONOutput = liftIO $ flushed json
|
||||
|
||||
outputError :: String -> Annex ()
|
||||
outputError s = withOutputType go
|
||||
where
|
||||
go (ConcurrentOutput _) = liftIO $
|
||||
#ifdef WITH_CONCURRENTOUTPUT
|
||||
errorConcurrent s
|
||||
#else
|
||||
q
|
||||
#endif
|
||||
go (ConcurrentOutput _) = concurrentMessage True s (go NormalOutput)
|
||||
go _ = liftIO $ do
|
||||
hFlush stdout
|
||||
hPutStr stderr s
|
||||
|
@ -52,5 +49,76 @@ q = noop
|
|||
flushed :: IO () -> IO ()
|
||||
flushed a = a >> hFlush stdout
|
||||
|
||||
withOutputType :: (OutputType -> Annex a) -> Annex a
|
||||
withOutputType a = outputType <$> Annex.getState Annex.output >>= a
|
||||
{- Outputs a message in a concurrency safe way.
|
||||
-
|
||||
- The message may be an error message, in which case it goes to stderr.
|
||||
-
|
||||
- When built without concurrent-output support, the fallback action is run
|
||||
- instead.
|
||||
-}
|
||||
concurrentMessage :: Bool -> String -> Annex () -> Annex ()
|
||||
#ifdef WITH_CONCURRENTOUTPUT
|
||||
concurrentMessage iserror msg _ = go =<< Annex.getState Annex.consoleregion
|
||||
where
|
||||
go Nothing
|
||||
| iserror = liftIO $ Console.errorConcurrent msg
|
||||
| otherwise = liftIO $ Console.outputConcurrent msg
|
||||
go (Just r) = do
|
||||
-- Can't display the error to stdout while
|
||||
-- console regions are in use, so set the errflag
|
||||
-- to get it to display to stderr later.
|
||||
when iserror $
|
||||
Annex.changeState $ \s -> s { Annex.consoleregionerrflag = True }
|
||||
liftIO $ Regions.appendConsoleRegion r msg
|
||||
#else
|
||||
concurrentMessage _ _ fallback = fallback
|
||||
#endif
|
||||
|
||||
{- Enable concurrent output when that has been requested.
|
||||
-
|
||||
- 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
|
||||
withConcurrentOutput a = withOutputType go
|
||||
where
|
||||
go (ConcurrentOutput _) = Console.withConcurrentOutput a
|
||||
go _ = a
|
||||
#else
|
||||
withConcurrentOutput = id
|
||||
#endif
|
||||
|
||||
{- Runs an action in its own dedicated region of the console.
|
||||
-
|
||||
- The region is closed at the end or on exception, and at that point
|
||||
- the value of the region is displayed in the scrolling area above
|
||||
- any other active regions.
|
||||
-
|
||||
- When not at a console, a region is not displayed until the end.
|
||||
-}
|
||||
inOwnConsoleRegion :: Annex a -> Annex a
|
||||
#ifdef WITH_CONCURRENTOUTPUT
|
||||
inOwnConsoleRegion a = Regions.withConsoleRegion Regions.Linear $ \r -> do
|
||||
setregion (Just r)
|
||||
a `finally` removeregion r
|
||||
where
|
||||
setregion v = Annex.changeState $ \s -> s { Annex.consoleregion = v }
|
||||
removeregion r = do
|
||||
errflag <- Annex.getState Annex.consoleregionerrflag
|
||||
let h = if errflag then Console.StdErr else Console.StdOut
|
||||
Annex.changeState $ \s -> s { Annex.consoleregionerrflag = False }
|
||||
setregion Nothing
|
||||
liftIO $ atomically $ do
|
||||
t <- Regions.getConsoleRegion r
|
||||
Regions.closeConsoleRegion r
|
||||
Console.bufferOutputSTM h $
|
||||
Console.toOutput (t <> fromString "\n")
|
||||
#else
|
||||
inOwnConsoleRegion = id
|
||||
#endif
|
||||
|
||||
#ifdef WITH_CONCURRENTOUTPUT
|
||||
instance Regions.LiftRegion Annex where
|
||||
liftRegion = liftIO . atomically
|
||||
#endif
|
||||
|
|
|
@ -279,7 +279,7 @@ Executable git-annex
|
|||
CPP-Options: -DWITH_DATABASE
|
||||
|
||||
if flag(ConcurrentOutput)
|
||||
Build-Depends: concurrent-output (>= 1.4.1)
|
||||
Build-Depends: concurrent-output (>= 1.5)
|
||||
CPP-Options: -DWITH_CONCURRENTOUTPUT
|
||||
|
||||
if flag(EKG)
|
||||
|
|
Loading…
Reference in a new issue