module System.ProgressBar.State
(
ProgressBar
, progressBar
, autoProgressBar
, hProgressBar
, mkProgressBar
, Progress(..)
, HasProgress(..)
, Label
, noLabel
, msg
, percentage
, exact
, ProgressRef
, startProgress
, incProgress
) where
import "async" Control.Concurrent.Async ( Async, async )
import "base" Control.Monad ( when )
import "base" Data.List ( genericLength, genericReplicate )
import "base" Data.Ratio ( (%) )
import "base" System.IO ( Handle, stderr, hPutChar, hPutStr, hFlush )
import "base" Text.Printf ( printf )
import "stm" Control.Concurrent.STM
( TVar, readTVar, writeTVar, newTVar, atomically, STM )
import "stm-chans" Control.Concurrent.STM.TMQueue
( TMQueue, readTMQueue, closeTMQueue, writeTMQueue, newTMQueue )
import qualified "terminal-size" System.Console.Terminal.Size as TS
type ProgressBar s a
= Label s
-> Label s
-> Integer
-> s
-> a
progressBar :: (HasProgress s) => ProgressBar s (IO ())
progressBar = hProgressBar stderr
autoProgressBar :: (HasProgress s) => ProgressBar s (IO ())
autoProgressBar mkPreLabel mkPostLabel defaultWidth st = do
mbWindow <- TS.size
let width = maybe defaultWidth TS.width mbWindow
progressBar mkPreLabel mkPostLabel width st
hProgressBar :: HasProgress s => Handle -> ProgressBar s (IO ())
hProgressBar hndl mkPreLabel mkPostLabel width st = do
hPutChar hndl '\r'
hPutStr hndl $ mkProgressBar mkPreLabel mkPostLabel width st
hFlush hndl
mkProgressBar :: (HasProgress s) => ProgressBar s String
mkProgressBar mkPreLabel mkPostLabel width st =
printf "%s%s[%s%s%s]%s%s"
preLabel
prePad
(genericReplicate completed '=')
(if remaining /= 0 && completed /= 0 then ">" else "")
(genericReplicate (remaining if completed /= 0 then 1 else 0)
'.'
)
postPad
postLabel
where
progress = getProgress st
todo = progressTodo progress
done = progressDone progress
fraction :: Rational
fraction | todo /= 0 = done % todo
| otherwise = 0 % 1
effectiveWidth = max 0 $ width usedSpace
usedSpace = 2 + genericLength preLabel
+ genericLength postLabel
+ genericLength prePad
+ genericLength postPad
numCompletedChars :: Rational
numCompletedChars = fraction * (effectiveWidth % 1)
completed, remaining :: Integer
completed = min effectiveWidth $ floor numCompletedChars
remaining = effectiveWidth completed
preLabel, postLabel :: String
preLabel = mkPreLabel st
postLabel = mkPostLabel st
prePad, postPad :: String
prePad = pad preLabel
postPad = pad postLabel
pad :: String -> String
pad s | null s = ""
| otherwise = " "
data Progress
= Progress
{ progressDone :: !Integer
, progressTodo :: !Integer
}
class HasProgress a where
getProgress :: a -> Progress
instance HasProgress Progress where
getProgress = id
type Label s
= s
-> String
noLabel :: Label s
noLabel = msg ""
msg :: String -> Label s
msg s _ = s
percentage :: HasProgress s => Label s
percentage s
| todo == 0 = "100%"
| otherwise = printf "%3i%%" (round (done % todo * 100) :: Integer)
where
done = progressDone progress
todo = progressTodo progress
progress = getProgress s
exact :: HasProgress s => Label s
exact s = printf "%*i/%s" (length totalStr) done totalStr
where
totalStr = show todo
done = progressDone progress
todo = progressTodo progress
progress = getProgress s
data ProgressRef s
= ProgressRef
{ prPrefix :: !(Label s)
, prPostfix :: !(Label s)
, prWidth :: !Integer
, prState :: !(TVar s)
, prQueue :: !(TMQueue (s -> s))
}
startProgress
:: (HasProgress s)
=> Label s
-> Label s
-> Integer
-> s
-> IO (ProgressRef s, Async ())
startProgress mkPreLabel mkPostLabel width st = do
pr <- buildProgressRef
a <- async $ reportProgress pr
return (pr, a)
where
buildProgressRef = do
tvSt <- atomically $ newTVar st
queue <- atomically $ newTMQueue
return $ ProgressRef mkPreLabel mkPostLabel width tvSt queue
incProgress :: ProgressRef s -> (s -> s) -> IO ()
incProgress progressRef =
atomically . writeTMQueue (prQueue progressRef)
reportProgress :: (HasProgress s) => ProgressRef s -> IO ()
reportProgress pr = do
continue <- atomically $ updateProgress pr
renderProgress pr
when continue $ reportProgress pr
updateProgress :: (HasProgress s) => ProgressRef s -> STM Bool
updateProgress pr =
maybe dontContinue doUpdate =<< readTMQueue (prQueue pr)
where
dontContinue = return False
doUpdate updateState = do
st <- readTVar $ prState pr
let newState = updateState st
progress = getProgress newState
todo = progressTodo progress
done = progressDone progress
let newDone = min todo $ max 0 done
writeTVar (prState pr) newState
if newDone >= todo
then closeTMQueue (prQueue pr) >> dontContinue
else return True
renderProgress :: (HasProgress s) => ProgressRef s -> IO ()
renderProgress pr = do
st <- atomically $ readTVar $ prState pr
autoProgressBar
(prPrefix pr)
(prPostfix pr)
(prWidth pr)
st