git-annex/Messages/Progress.hs
Joey Hess 40ecf58d4b
update licenses from GPL to AGPL
This does not change the overall license of the git-annex program, which
was already AGPL due to a number of sources files being AGPL already.

Legally speaking, I'm adding a new license under which these files are
now available; I already released their current contents under the GPL
license. Now they're dual licensed GPL and AGPL. However, I intend
for all my future changes to these files to only be released under the
AGPL license, and I won't be tracking the dual licensing status, so I'm
simply changing the license statement to say it's AGPL.

(In some cases, others wrote parts of the code of a file and released it
under the GPL; but in all cases I have contributed a significant portion
of the code in each file and it's that code that is getting the AGPL
license; the GPL license of other contributors allows combining with
AGPL code.)
2019-03-13 15:48:14 -04:00

130 lines
4.2 KiB
Haskell

{- git-annex progress output
-
- Copyright 2010-2015 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module Messages.Progress where
import Common
import Messages
import Utility.Metered
import Types
import Types.Messages
import Types.Key
import qualified Messages.JSON as JSON
import Messages.Concurrent
import qualified System.Console.Regions as Regions
import qualified System.Console.Concurrent as Console
{- Shows a progress meter while performing a transfer of a key.
- The action is passed the meter and a callback to use to update the meter.
-
- When the key's size is not known, the srcfile is statted to get the size.
- This allows uploads of keys without size to still have progress
- displayed.
--}
metered :: Maybe MeterUpdate -> Key -> Annex (Maybe FilePath) -> (Meter -> MeterUpdate -> Annex a) -> Annex a
metered othermeter key getsrcfile a = withMessageState $ \st ->
flip go st =<< getsz
where
go _ (MessageState { outputType = QuietOutput }) = nometer
go msize (MessageState { outputType = NormalOutput, concurrentOutputEnabled = False }) = do
showOutput
meter <- liftIO $ mkMeter msize $
displayMeterHandle stdout bandwidthMeter
m <- liftIO $ rateLimitMeterUpdate 0.2 meter $
updateMeter meter
r <- a meter (combinemeter m)
liftIO $ clearMeterHandle meter stdout
return r
go msize (MessageState { outputType = NormalOutput, concurrentOutputEnabled = True }) =
withProgressRegion $ \r -> do
meter <- liftIO $ mkMeter msize $ \_ msize' old new ->
let s = bandwidthMeter msize' old new
in Regions.setConsoleRegion r ('\n' : s)
m <- liftIO $ rateLimitMeterUpdate 0.2 meter $
updateMeter meter
a meter (combinemeter m)
go msize (MessageState { outputType = JSONOutput jsonoptions })
| jsonProgress jsonoptions = do
buf <- withMessageState $ return . jsonBuffer
meter <- liftIO $ mkMeter msize $ \_ msize' _old (new, _now) ->
JSON.progress buf msize' new
m <- liftIO $ rateLimitMeterUpdate 0.1 meter $
updateMeter meter
a meter (combinemeter m)
| otherwise = nometer
nometer = do
dummymeter <- liftIO $ mkMeter Nothing $
\_ _ _ _ -> return ()
a dummymeter (combinemeter (const noop))
combinemeter m = case othermeter of
Nothing -> m
Just om -> combineMeterUpdate m om
getsz = case keySize key of
Just sz -> return (Just sz)
Nothing -> do
srcfile <- getsrcfile
case srcfile of
Nothing -> return Nothing
Just f -> catchMaybeIO $ liftIO $ getFileSize f
{- Poll file size to display meter. -}
meteredFile :: FilePath -> Maybe MeterUpdate -> Key -> Annex a -> Annex a
meteredFile file combinemeterupdate key a =
metered combinemeterupdate key (return Nothing) $ \_ p ->
watchFileSize file p a
{- Progress dots. -}
showProgressDots :: Annex ()
showProgressDots = outputMessage JSON.none "."
{- Runs a command, that may output progress to either stdout or
- stderr, as well as other messages.
-
- In quiet mode, the output is suppressed, except for error messages.
-}
progressCommand :: FilePath -> [CommandParam] -> Annex Bool
progressCommand cmd params = progressCommandEnv cmd params Nothing
progressCommandEnv :: FilePath -> [CommandParam] -> Maybe [(String, String)] -> Annex Bool
progressCommandEnv cmd params environ = ifM commandProgressDisabled
( do
oh <- mkOutputHandler
liftIO $ demeterCommandEnv oh cmd params environ
, liftIO $ boolSystemEnv cmd params environ
)
mkOutputHandler :: Annex OutputHandler
mkOutputHandler = OutputHandler
<$> commandProgressDisabled
<*> mkStderrEmitter
mkOutputHandlerQuiet :: Annex OutputHandler
mkOutputHandlerQuiet = OutputHandler
<$> pure True
<*> mkStderrEmitter
mkStderrRelayer :: Annex (Handle -> IO ())
mkStderrRelayer = do
quiet <- commandProgressDisabled
emitter <- mkStderrEmitter
return $ \h -> avoidProgress quiet h emitter
{- Generates an IO action that can be used to emit stderr.
-
- When a progress meter is displayed, this takes care to avoid
- messing it up with interleaved stderr from a command.
-}
mkStderrEmitter :: Annex (String -> IO ())
mkStderrEmitter = withMessageState go
where
go s
| concurrentOutputEnabled s = return Console.errorConcurrent
| otherwise = return (hPutStrLn stderr)