{-# LANGUAGE ScopedTypeVariables #-}
module Data.ByteString.Lazy.Progress(
trackProgress
, trackProgressWithChunkSize
, trackProgressString
, trackProgressStringWithChunkSize
, bytesToUnittedStr
)
where
import Control.Applicative ((<$>))
import qualified Data.ByteString as BSS
import Data.ByteString.Lazy(ByteString)
import qualified Data.ByteString.Lazy as BS
import Data.Maybe (isJust)
import Data.Time.Clock (getCurrentTime,diffUTCTime,UTCTime)
import Data.Word (Word64)
import System.IO.Unsafe (unsafeInterleaveIO)
trackProgress :: (Word64 -> Word64 -> IO ()) ->
ByteString ->
IO ByteString
trackProgress tracker inputBS =
BS.fromChunks <$> runTrack 0 (BS.toChunks inputBS)
where
runTrack _ [] = return []
runTrack x (fst:rest) = unsafeInterleaveIO $ do
let amtRead = fromIntegral $ BSS.length fst
tracker amtRead (x + amtRead)
(fst :) <$> runTrack (x + amtRead) rest
trackProgressWithChunkSize :: Word64 -> (Word64 -> Word64 -> IO ()) ->
ByteString ->
IO ByteString
trackProgressWithChunkSize chunkSize tracker inputBS = runLoop 0 inputBS
where
runLoop x bstr | BS.null bstr = return BS.empty
| otherwise = unsafeInterleaveIO $ do
let (first,rest) = BS.splitAt (fromIntegral chunkSize) bstr
amtRead = fromIntegral (BS.length first)
tracker amtRead (x + amtRead)
(first `BS.append`) <$> runLoop (x + amtRead) rest
trackProgressString :: String -> Maybe Word64 -> (String -> IO ()) ->
IO (ByteString -> IO ByteString)
trackProgressString formatStr mTotal tracker = do
startTime <- getCurrentTime
return (trackProgress (handler startTime))
where
handler startTime chunkSize total = do
now <- getCurrentTime
tracker (buildString formatStr startTime now mTotal chunkSize total)
trackProgressStringWithChunkSize :: String
-> Word64
-> Maybe Word64
-> (String -> IO ())
-> IO (ByteString -> IO ByteString)
trackProgressStringWithChunkSize formatStr chunk mTotal tracker = do
startTime <- getCurrentTime
return (trackProgressWithChunkSize chunk (handler startTime))
where
handler startTime chunkSize total = do
now <- getCurrentTime
tracker (buildString formatStr startTime now mTotal chunkSize total)
buildString :: String ->
UTCTime -> UTCTime -> Maybe Word64 -> Word64 -> Word64 ->
String
buildString form startTime curTime mTotal chunkSize amtRead = subPercents form
where
per_b = show amtRead
per_B = bytesToUnittedStr amtRead
per_c = show chunkSize
per_C = bytesToUnittedStr chunkSize
diff = max 1 (round $ toRational $ diffUTCTime curTime startTime)
rate = amtRead `div` diff
per_r = show rate
per_R = bytesToUnittedStr rate ++ "ps"
total = case mTotal of
Just t -> t
Nothing -> error "INTERNAL ERROR (needed total w/ Nothing)"
tleft = (total - amtRead) `div` rate
per_t = show tleft
hLeft = tleft `div` (60 * 60)
mLeft = (tleft `div` 60) `mod` 60
sLeft = tleft `mod` 60
per_T = showPadded hLeft ++ ":" ++ showPadded mLeft ++
":" ++ showPadded sLeft
perc = 100 * (fromIntegral amtRead / fromIntegral total) :: Double
per_p = show (round perc) ++ "%"
oktot = isJust mTotal
subPercents [] = []
subPercents ('%':rest) = subPercents' rest
subPercents (x:rest) = x : subPercents rest
subPercents' [] = []
subPercents' ('b':rest) = per_b ++ subPercents rest
subPercents' ('B':rest) = per_B ++ subPercents rest
subPercents' ('c':rest) = per_c ++ subPercents rest
subPercents' ('C':rest) = per_C ++ subPercents rest
subPercents' ('r':rest) = per_r ++ subPercents rest
subPercents' ('R':rest) = per_R ++ subPercents rest
subPercents' ('t':rest) | oktot = per_t ++ subPercents rest
subPercents' ('T':rest) | oktot = per_T ++ subPercents rest
subPercents' ('p':rest) | oktot = per_p ++ subPercents rest
subPercents' ('%':rest) = "%" ++ subPercents rest
subPercents' (x:rest) = '%' : ('x' : subPercents rest)
showPadded :: Show a => a -> String
showPadded x = prefix ++ base
where
base = show x
prefix = case base of
[] -> "00"
[x] -> "0"
_ -> ""
bytesToUnittedStr :: Word64 -> String
bytesToUnittedStr x
| x < bk_brk = show x ++ "b"
| x < km_brk = showHundredthsDiv x k ++ "k"
| x < mg_brk = showHundredthsDiv x m ++ "m"
| otherwise = showHundredthsDiv x g ++ "g"
where
bk_brk = 4096
km_brk = 768 * k
mg_brk = 768 * m
k = 1024
m = 1024 * k
g = 1024 * m
showHundredthsDiv _ 0 = error "Should never happen!"
showHundredthsDiv amt size = show ones ++ "." ++ show tenths ++ show hundreths
where
divRes :: Double = fromIntegral amt / fromIntegral size
divRes100 = round (divRes * 100)
ones = divRes100 `div` 100
tenths = (divRes100 `div` 10) `mod` 10
hundreths = divRes100 `mod` 10