module System.ProgressBar
(
ProgressBar
, progressBar
, hProgressBar
, mkProgressBar
, Label
, noLabel
, msg
, percentage
, exact
, ProgressRef
, startProgress
, incProgress
) where
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 "base" Control.Concurrent ( ThreadId, forkIO )
import "stm" Control.Concurrent.STM
( TVar, readTVar, writeTVar, newTVar, atomically, STM )
import "stm-chans" Control.Concurrent.STM.TMQueue
( TMQueue, readTMQueue, closeTMQueue, writeTMQueue, newTMQueue )
type ProgressBar a
= Label
-> Label
-> Integer
-> Integer
-> Integer
-> a
progressBar :: ProgressBar (IO ())
progressBar = hProgressBar stderr
hProgressBar :: Handle -> ProgressBar (IO ())
hProgressBar hndl mkPreLabel mkPostLabel width todo done = do
hPutChar hndl '\r'
hPutStr hndl $ mkProgressBar mkPreLabel mkPostLabel width todo done
hFlush hndl
mkProgressBar :: ProgressBar String
mkProgressBar mkPreLabel mkPostLabel width todo done =
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
fraction :: Rational
fraction | done /= 0 = todo % done
| 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 todo done
postLabel = mkPostLabel todo done
prePad, postPad :: String
prePad = pad preLabel
postPad = pad postLabel
pad :: String -> String
pad s | null s = ""
| otherwise = " "
type Label
= Integer
-> Integer
-> String
noLabel :: Label
noLabel = msg ""
msg :: String -> Label
msg s _ _ = s
percentage :: Label
percentage done todo = printf "%3i%%" (round (done % todo * 100) :: Integer)
exact :: Label
exact done total = printf "%*i/%s" (length totalStr) done totalStr
where
totalStr = show total
data ProgressRef
= ProgressRef
{ prPrefix :: Label
, prPostfix :: Label
, prWidth :: Integer
, prCompleted :: TVar Integer
, prTotal :: Integer
, prQueue :: TMQueue Integer
}
startProgress
:: Label
-> Label
-> Integer
-> Integer
-> IO (ProgressRef, ThreadId)
startProgress mkPreLabel mkPostLabel width total = do
pr <- buildProgressRef
tid <- forkIO $ reportProgress pr
return (pr, tid)
where
buildProgressRef = do
completed <- atomically $ newTVar 0
queue <- atomically $ newTMQueue
return $ ProgressRef mkPreLabel mkPostLabel width completed total queue
incProgress :: ProgressRef -> Integer -> IO ()
incProgress progressRef =
atomically . writeTMQueue (prQueue progressRef)
reportProgress :: ProgressRef -> IO ()
reportProgress pr = do
continue <- atomically $ updateProgress pr
renderProgress pr
when continue $ reportProgress pr
updateProgress :: ProgressRef -> STM Bool
updateProgress ProgressRef {prCompleted, prQueue, prTotal} = do
maybe dontContinue doUpdate =<< readTMQueue prQueue
where
dontContinue = return False
doUpdate countDiff = do
count <- readTVar prCompleted
let newCount = min prTotal $ max 0 $ count + countDiff
writeTVar prCompleted newCount
if newCount >= prTotal
then closeTMQueue prQueue >> dontContinue
else return True
renderProgress :: ProgressRef -> IO ()
renderProgress ProgressRef {..} = do
completed <- atomically $ readTVar prCompleted
progressBar prPrefix prPostfix prWidth completed prTotal