module System.Console.AsciiProgress.Internal
where
import Control.Concurrent (Chan, MVar, newChan, newEmptyMVar, newMVar,
readMVar, tryPutMVar, tryTakeMVar)
import Data.Default (Default (..))
import Data.Time.Clock
import Text.Printf
data Options = Options { pgFormat :: String
, pgCompletedChar :: Char
, pgPendingChar :: Char
, pgTotal :: Integer
, pgWidth :: Int
, pgOnCompletion :: Maybe String
, pgGetProgressStr :: Options -> Stats -> String
}
instance Default Options where
def = Options { pgFormat = "Working :percent [:bar] :current/:total " ++
"(for :elapsed, :eta remaining)"
, pgCompletedChar = '='
, pgPendingChar = ' '
, pgTotal = 20
, pgWidth = 80
, pgOnCompletion = Nothing
, pgGetProgressStr = getProgressStr
}
data ProgressBarInfo = ProgressBarInfo { pgOptions :: Options
, pgChannel :: Chan Integer
, pgCompleted :: MVar Integer
, pgFirstTick :: MVar UTCTime
}
data Stats = Stats { stTotal :: Integer
, stCompleted :: Integer
, stRemaining :: Integer
, stElapsed :: Double
, stPercent :: Double
, stEta :: Double
}
newProgressBarInfo :: Options -> IO ProgressBarInfo
newProgressBarInfo opts = do
chan <- newChan
mcompleted <- newMVar 0
mfirstTick <- newEmptyMVar
return $ ProgressBarInfo opts chan mcompleted mfirstTick
getProgressStr :: Options -> Stats -> String
getProgressStr Options{..} Stats{..} = replace ":bar" barStr statsStr
where
statsStr = replaceMany
[ (":elapsed", printf "%5.1f" stElapsed)
, (":current", printf "%3d" stCompleted)
, (":total" , printf "%3d" stTotal)
, (":percent", printf "%3d%%" (floor (100 * stPercent) :: Int))
, (":eta" , printf "%5.1f" stEta)
]
pgFormat
barWidth = pgWidth length (replace ":bar" "" statsStr)
barStr = getBar pgCompletedChar pgPendingChar barWidth stPercent
getInfoStats :: ProgressBarInfo -> IO Stats
getInfoStats info = do
completed <- readMVar (pgCompleted info)
currentTime <- getCurrentTime
initTime <- forceReadMVar (pgFirstTick info) currentTime
let total = pgTotal (pgOptions info)
remaining = total completed
elapsed = getElapsed initTime currentTime
percent = fromIntegral completed / fromIntegral total
eta = getEta completed remaining elapsed
return $ Stats total completed remaining elapsed percent eta
getBar :: Char -> Char -> Int -> Double -> String
getBar completedChar pendingChar width percent =
replicate bcompleted completedChar ++ replicate bremaining pendingChar
where
fwidth = fromIntegral width
bcompleted = ceiling $ fwidth * percent
bremaining = width bcompleted
getElapsed :: UTCTime -> UTCTime -> Double
getElapsed initTime currentTime = realToFrac (diffUTCTime currentTime initTime)
getEta :: Integer -> Integer -> Double -> Double
getEta 0 _ _ = 0
getEta completed remaining elapsed = averageSecsPerTick * fromIntegral remaining
where
averageSecsPerTick = elapsed / fromIntegral completed
replaceMany :: Eq a => [([a], [a])] -> [a] -> [a]
replaceMany pairs target = foldr (uncurry replace) target pairs
replace :: Eq a => [a] -> [a] -> [a] -> [a]
replace _ _ [] = []
replace [] new target = new ++ target
replace old new target@(t:ts) =
if take len target == old
then new ++ replace old new (drop len target)
else t : replace old new ts
where len = length old
forceReadMVar :: MVar a -> a -> IO a
forceReadMVar mv v = tryTakeMVar mv >>= \m -> case m of
Nothing -> do
success <- tryPutMVar mv v
if success
then return v
else readMVar mv
Just o -> do
_ <- tryPutMVar mv o
return o