git-annex/Messages/Internal.hs
Joey Hess 067aabdd48
wip RawFilePath 2x git-annex find speedup
Finally builds (oh the agoncy of making it build), but still very
unmergable, only Command.Find is included and lots of stuff is badly
hacked to make it compile.

Benchmarking vs master, this git-annex find is significantly faster!
Specifically:

	num files	old	new	speedup
	48500		4.77	3.73	28%
	12500		1.36	1.02	66%
	20		0.075	0.074	0% (so startup time is unchanged)

That's without really finishing the optimization. Things still to do:

* Eliminate all the fromRawFilePath, toRawFilePath, encodeBS,
  decodeBS conversions.
* Use versions of IO actions like getFileStatus that take a RawFilePath.
* Eliminate some Data.ByteString.Lazy.toStrict, which is a slow copy.
* Use ByteString for parsing git config to speed up startup.

It's likely several of those will speed up git-annex find further.
And other commands will certianly benefit even more.
2019-11-26 16:01:58 -04:00

83 lines
2.5 KiB
Haskell

{- git-annex output messages, including concurrent output to display regions
-
- Copyright 2010-2018 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module Messages.Internal where
import Common
import Annex
import Types.Messages
import Messages.Concurrent
import qualified Messages.JSON as JSON
import Messages.JSON (JSONBuilder)
import qualified Data.ByteString as S
withMessageState :: (MessageState -> Annex a) -> Annex a
withMessageState a = Annex.getState Annex.output >>= a
outputMessage :: JSONBuilder -> S.ByteString -> Annex ()
outputMessage = outputMessage' bufferJSON
outputMessage' :: (JSONBuilder -> MessageState -> Annex Bool) -> JSONBuilder -> S.ByteString -> Annex ()
outputMessage' jsonoutputter jsonbuilder msg = withMessageState $ \s -> case outputType s of
NormalOutput
| concurrentOutputEnabled s -> concurrentMessage s False (decodeBS msg) q
| otherwise -> liftIO $ flushed $ S.putStr msg
JSONOutput _ -> void $ jsonoutputter jsonbuilder s
QuietOutput -> q
-- Buffer changes to JSON until end is reached and then emit it.
bufferJSON :: JSONBuilder -> MessageState -> Annex Bool
bufferJSON jsonbuilder s = case outputType s of
JSONOutput jsonoptions
| endjson -> do
Annex.changeState $ \st ->
st { Annex.output = s { jsonBuffer = Nothing } }
maybe noop (liftIO . flushed . JSON.emit . JSON.finalize jsonoptions) json
return True
| otherwise -> do
Annex.changeState $ \st ->
st { Annex.output = s { jsonBuffer = json } }
return True
_ -> return False
where
(json, endjson) = case jsonbuilder i of
Nothing -> (jsonBuffer s, False)
(Just (j, e)) -> (Just j, e)
i = case jsonBuffer s of
Nothing -> Nothing
Just b -> Just (b, False)
-- Immediately output JSON.
outputJSON :: JSONBuilder -> MessageState -> Annex Bool
outputJSON jsonbuilder s = case outputType s of
JSONOutput _ -> do
maybe noop (liftIO . flushed . JSON.emit)
(fst <$> jsonbuilder Nothing)
return True
_ -> return False
outputError :: String -> Annex ()
outputError msg = withMessageState $ \s -> case (outputType s, jsonBuffer s) of
(JSONOutput jsonoptions, Just jb) | jsonErrorMessages jsonoptions ->
let jb' = Just (JSON.addErrorMessage (lines msg) jb)
in Annex.changeState $ \st ->
st { Annex.output = s { jsonBuffer = jb' } }
_
| concurrentOutputEnabled s -> concurrentMessage s True msg go
| otherwise -> go
where
go = liftIO $ do
hFlush stdout
hPutStr stderr msg
hFlush stderr
q :: Monad m => m ()
q = noop
flushed :: IO () -> IO ()
flushed a = a >> hFlush stdout