{-# LANGUAGE Safe #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module Data.Progress.Tracker (
newProgress, newProgress',
addCallback, addParent,
incrP, incrP', setP, setP', incrTotal,
setTotal, finishP,
getSpeed,
withStatus,
getETR,
getETA,
ProgressStatus(..),
Progress, ProgressTimeSource,
ProgressCallback,
ProgressStatuses,
defaultTimeSource
)
where
import safe Control.Concurrent.MVar
( modifyMVar_, withMVar, newMVar, MVar )
import safe System.Time ( getClockTime )
import safe System.Time.Utils ( clockTimeToEpoch )
import safe Data.Ratio ( (%) )
type ProgressTimeSource = IO Integer
type ProgressCallback = ProgressStatus -> ProgressStatus -> IO ()
data ProgressStatus =
ProgressStatus {ProgressStatus -> Integer
completedUnits :: Integer,
ProgressStatus -> Integer
totalUnits :: Integer,
ProgressStatus -> Integer
startTime :: Integer,
ProgressStatus -> String
trackerName :: String,
ProgressStatus -> ProgressTimeSource
timeSource :: ProgressTimeSource
}
data ProgressRecord =
ProgressRecord {ProgressRecord -> [Progress]
parents :: [Progress],
ProgressRecord -> [ProgressCallback]
callbacks :: [ProgressCallback],
ProgressRecord -> ProgressStatus
status :: ProgressStatus}
newtype Progress = Progress (MVar ProgressRecord)
class ProgressStatuses a b where
withStatus :: a -> (ProgressStatus -> b) -> b
instance ProgressStatuses Progress (IO b) where
withStatus :: Progress -> (ProgressStatus -> IO b) -> IO b
withStatus (Progress MVar ProgressRecord
x) ProgressStatus -> IO b
func = MVar ProgressRecord -> (ProgressRecord -> IO b) -> IO b
forall a b. MVar a -> (a -> IO b) -> IO b
withMVar MVar ProgressRecord
x (\ProgressRecord
y -> ProgressStatus -> IO b
func (ProgressRecord -> ProgressStatus
status ProgressRecord
y))
instance ProgressStatuses ProgressStatus b where
withStatus :: ProgressStatus -> (ProgressStatus -> b) -> b
withStatus ProgressStatus
x ProgressStatus -> b
func = ProgressStatus -> b
func ProgressStatus
x
newProgress :: String
-> Integer
-> IO Progress
newProgress :: String -> Integer -> IO Progress
newProgress String
name Integer
total =
do Integer
t <- ProgressTimeSource
defaultTimeSource
ProgressStatus -> [ProgressCallback] -> IO Progress
newProgress' (ProgressStatus {completedUnits :: Integer
completedUnits = Integer
0, totalUnits :: Integer
totalUnits = Integer
total,
startTime :: Integer
startTime = Integer
t, trackerName :: String
trackerName = String
name,
timeSource :: ProgressTimeSource
timeSource = ProgressTimeSource
defaultTimeSource})
[]
newProgress' :: ProgressStatus
-> [ProgressCallback] -> IO Progress
newProgress' :: ProgressStatus -> [ProgressCallback] -> IO Progress
newProgress' ProgressStatus
news [ProgressCallback]
newcb =
do MVar ProgressRecord
r <- ProgressRecord -> IO (MVar ProgressRecord)
forall a. a -> IO (MVar a)
newMVar (ProgressRecord -> IO (MVar ProgressRecord))
-> ProgressRecord -> IO (MVar ProgressRecord)
forall a b. (a -> b) -> a -> b
$ ProgressRecord {parents :: [Progress]
parents = [],
callbacks :: [ProgressCallback]
callbacks = [ProgressCallback]
newcb, status :: ProgressStatus
status = ProgressStatus
news}
Progress -> IO Progress
forall (m :: * -> *) a. Monad m => a -> m a
return (MVar ProgressRecord -> Progress
Progress MVar ProgressRecord
r)
addCallback :: Progress -> ProgressCallback -> IO ()
addCallback :: Progress -> ProgressCallback -> IO ()
addCallback (Progress MVar ProgressRecord
mpo) ProgressCallback
cb = MVar ProgressRecord
-> (ProgressRecord -> IO ProgressRecord) -> IO ()
forall a. MVar a -> (a -> IO a) -> IO ()
modifyMVar_ MVar ProgressRecord
mpo ((ProgressRecord -> IO ProgressRecord) -> IO ())
-> (ProgressRecord -> IO ProgressRecord) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ProgressRecord
po ->
ProgressRecord -> IO ProgressRecord
forall (m :: * -> *) a. Monad m => a -> m a
return (ProgressRecord -> IO ProgressRecord)
-> ProgressRecord -> IO ProgressRecord
forall a b. (a -> b) -> a -> b
$ ProgressRecord
po {callbacks :: [ProgressCallback]
callbacks = ProgressCallback
cb ProgressCallback -> [ProgressCallback] -> [ProgressCallback]
forall a. a -> [a] -> [a]
: ProgressRecord -> [ProgressCallback]
callbacks ProgressRecord
po}
addParent :: Progress
-> Progress
-> IO ()
addParent :: Progress -> Progress -> IO ()
addParent (Progress MVar ProgressRecord
mcpo) Progress
ppo = MVar ProgressRecord
-> (ProgressRecord -> IO ProgressRecord) -> IO ()
forall a. MVar a -> (a -> IO a) -> IO ()
modifyMVar_ MVar ProgressRecord
mcpo ((ProgressRecord -> IO ProgressRecord) -> IO ())
-> (ProgressRecord -> IO ProgressRecord) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ProgressRecord
cpo ->
do Progress -> Integer -> IO ()
incrP' Progress
ppo (ProgressStatus -> Integer
completedUnits (ProgressStatus -> Integer)
-> (ProgressRecord -> ProgressStatus) -> ProgressRecord -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgressRecord -> ProgressStatus
status (ProgressRecord -> Integer) -> ProgressRecord -> Integer
forall a b. (a -> b) -> a -> b
$ ProgressRecord
cpo)
Progress -> Integer -> IO ()
incrTotal Progress
ppo (ProgressStatus -> Integer
totalUnits (ProgressStatus -> Integer)
-> (ProgressRecord -> ProgressStatus) -> ProgressRecord -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgressRecord -> ProgressStatus
status (ProgressRecord -> Integer) -> ProgressRecord -> Integer
forall a b. (a -> b) -> a -> b
$ ProgressRecord
cpo)
ProgressRecord -> IO ProgressRecord
forall (m :: * -> *) a. Monad m => a -> m a
return (ProgressRecord -> IO ProgressRecord)
-> ProgressRecord -> IO ProgressRecord
forall a b. (a -> b) -> a -> b
$ ProgressRecord
cpo {parents :: [Progress]
parents = Progress
ppo Progress -> [Progress] -> [Progress]
forall a. a -> [a] -> [a]
: ProgressRecord -> [Progress]
parents ProgressRecord
cpo}
finishP :: Progress -> IO ()
finishP :: Progress -> IO ()
finishP (Progress MVar ProgressRecord
mp) =
MVar ProgressRecord
-> (ProgressRecord -> IO ProgressRecord) -> IO ()
forall a. MVar a -> (a -> IO a) -> IO ()
modifyMVar_ MVar ProgressRecord
mp ProgressRecord -> IO ProgressRecord
modfunc
where modfunc :: ProgressRecord -> IO ProgressRecord
modfunc :: ProgressRecord -> IO ProgressRecord
modfunc ProgressRecord
oldpr =
do let adjustment :: Integer
adjustment = (ProgressStatus -> Integer
completedUnits (ProgressStatus -> Integer)
-> (ProgressRecord -> ProgressStatus) -> ProgressRecord -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgressRecord -> ProgressStatus
status (ProgressRecord -> Integer) -> ProgressRecord -> Integer
forall a b. (a -> b) -> a -> b
$ ProgressRecord
oldpr)
Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- (ProgressStatus -> Integer
totalUnits (ProgressStatus -> Integer)
-> (ProgressRecord -> ProgressStatus) -> ProgressRecord -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgressRecord -> ProgressStatus
status (ProgressRecord -> Integer) -> ProgressRecord -> Integer
forall a b. (a -> b) -> a -> b
$ ProgressRecord
oldpr)
ProgressRecord -> (Progress -> IO ()) -> IO ()
callParents ProgressRecord
oldpr (\Progress
x -> Progress -> Integer -> IO ()
incrTotal Progress
x Integer
adjustment)
ProgressRecord -> IO ProgressRecord
forall (m :: * -> *) a. Monad m => a -> m a
return (ProgressRecord -> IO ProgressRecord)
-> ProgressRecord -> IO ProgressRecord
forall a b. (a -> b) -> a -> b
$ ProgressRecord
oldpr {status :: ProgressStatus
status = (ProgressRecord -> ProgressStatus
status ProgressRecord
oldpr)
{totalUnits :: Integer
totalUnits = ProgressStatus -> Integer
completedUnits (ProgressStatus -> Integer)
-> (ProgressRecord -> ProgressStatus) -> ProgressRecord -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgressRecord -> ProgressStatus
status (ProgressRecord -> Integer) -> ProgressRecord -> Integer
forall a b. (a -> b) -> a -> b
$ ProgressRecord
oldpr}}
incrP :: Progress -> Integer -> IO ()
incrP :: Progress -> Integer -> IO ()
incrP Progress
po Integer
count = Progress -> (ProgressStatus -> ProgressStatus) -> IO ()
modStatus Progress
po ProgressStatus -> ProgressStatus
statusfunc
where statusfunc :: ProgressStatus -> ProgressStatus
statusfunc ProgressStatus
s =
ProgressStatus
s {completedUnits :: Integer
completedUnits = ProgressStatus -> Integer
newcu ProgressStatus
s,
totalUnits :: Integer
totalUnits = if ProgressStatus -> Integer
newcu ProgressStatus
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> ProgressStatus -> Integer
totalUnits ProgressStatus
s
then ProgressStatus -> Integer
newcu ProgressStatus
s
else ProgressStatus -> Integer
totalUnits ProgressStatus
s}
newcu :: ProgressStatus -> Integer
newcu ProgressStatus
s = ProgressStatus -> Integer
completedUnits ProgressStatus
s Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
count
incrP' :: Progress -> Integer -> IO ()
incrP' :: Progress -> Integer -> IO ()
incrP' Progress
po Integer
count =
Progress -> (ProgressStatus -> ProgressStatus) -> IO ()
modStatus Progress
po (\ProgressStatus
s -> ProgressStatus
s {completedUnits :: Integer
completedUnits = ProgressStatus -> Integer
completedUnits ProgressStatus
s Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
count})
setP :: Progress -> Integer -> IO ()
setP :: Progress -> Integer -> IO ()
setP Progress
po Integer
count = Progress -> (ProgressStatus -> ProgressStatus) -> IO ()
modStatus Progress
po ProgressStatus -> ProgressStatus
statusfunc
where statusfunc :: ProgressStatus -> ProgressStatus
statusfunc ProgressStatus
s =
ProgressStatus
s {completedUnits :: Integer
completedUnits = Integer
count,
totalUnits :: Integer
totalUnits = if Integer
count Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> ProgressStatus -> Integer
totalUnits ProgressStatus
s
then Integer
count
else ProgressStatus -> Integer
totalUnits ProgressStatus
s}
setP' :: Progress -> Integer -> IO ()
setP' :: Progress -> Integer -> IO ()
setP' Progress
po Integer
count = Progress -> (ProgressStatus -> ProgressStatus) -> IO ()
modStatus Progress
po (\ProgressStatus
s -> ProgressStatus
s {completedUnits :: Integer
completedUnits = Integer
count})
incrTotal :: Progress -> Integer -> IO ()
incrTotal :: Progress -> Integer -> IO ()
incrTotal Progress
po Integer
count =
Progress -> (ProgressStatus -> ProgressStatus) -> IO ()
modStatus Progress
po (\ProgressStatus
s -> ProgressStatus
s {totalUnits :: Integer
totalUnits = ProgressStatus -> Integer
totalUnits ProgressStatus
s Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
count})
setTotal :: Progress -> Integer -> IO ()
setTotal :: Progress -> Integer -> IO ()
setTotal Progress
po Integer
count =
Progress -> (ProgressStatus -> ProgressStatus) -> IO ()
modStatus Progress
po (\ProgressStatus
s -> ProgressStatus
s {totalUnits :: Integer
totalUnits = Integer
count})
getSpeed :: (ProgressStatuses a (IO b), Fractional b) => a -> IO b
getSpeed :: forall a b. (ProgressStatuses a (IO b), Fractional b) => a -> IO b
getSpeed a
po = a -> (ProgressStatus -> IO b) -> IO b
forall a b. ProgressStatuses a b => a -> (ProgressStatus -> b) -> b
withStatus a
po ((ProgressStatus -> IO b) -> IO b)
-> (ProgressStatus -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \ProgressStatus
status ->
do Integer
t <- ProgressStatus -> ProgressTimeSource
timeSource ProgressStatus
status
let elapsed :: Integer
elapsed = Integer
t Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- (ProgressStatus -> Integer
startTime ProgressStatus
status)
b -> IO b
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> IO b) -> b -> IO b
forall a b. (a -> b) -> a -> b
$ if Integer
elapsed Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0
then Rational -> b
forall a. Fractional a => Rational -> a
fromRational Rational
0
else Rational -> b
forall a. Fractional a => Rational -> a
fromRational ((ProgressStatus -> Integer
completedUnits ProgressStatus
status) Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
elapsed)
getETR :: (ProgressStatuses a (IO Integer),
ProgressStatuses a (IO Rational)) => a -> IO Integer
getETR :: forall a.
(ProgressStatuses a ProgressTimeSource,
ProgressStatuses a (IO Rational)) =>
a -> ProgressTimeSource
getETR a
po =
do Rational
speed <- ((a -> IO Rational
forall a b. (ProgressStatuses a (IO b), Fractional b) => a -> IO b
getSpeed a
po)::IO Rational)
if Rational
speed Rational -> Rational -> Bool
forall a. Eq a => a -> a -> Bool
== Rational
0
then Integer -> ProgressTimeSource
forall (m :: * -> *) a. Monad m => a -> m a
return Integer
0
else
a -> (ProgressStatus -> ProgressTimeSource) -> ProgressTimeSource
forall a b. ProgressStatuses a b => a -> (ProgressStatus -> b) -> b
withStatus a
po ((ProgressStatus -> ProgressTimeSource) -> ProgressTimeSource)
-> (ProgressStatus -> ProgressTimeSource) -> ProgressTimeSource
forall a b. (a -> b) -> a -> b
$ \ProgressStatus
status ->
do let remaining :: Integer
remaining = ProgressStatus -> Integer
totalUnits ProgressStatus
status Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- ProgressStatus -> Integer
completedUnits ProgressStatus
status
Integer -> ProgressTimeSource
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> ProgressTimeSource) -> Integer -> ProgressTimeSource
forall a b. (a -> b) -> a -> b
$ Rational -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
round (Rational -> Integer) -> Rational -> Integer
forall a b. (a -> b) -> a -> b
$ (Integer -> Rational
forall a. Real a => a -> Rational
toRational Integer
remaining) Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ Rational
speed
getETA :: (ProgressStatuses a (IO Integer),
ProgressStatuses a (IO Rational)) => a -> IO Integer
getETA :: forall a.
(ProgressStatuses a ProgressTimeSource,
ProgressStatuses a (IO Rational)) =>
a -> ProgressTimeSource
getETA a
po =
do Integer
etr <- a -> ProgressTimeSource
forall a.
(ProgressStatuses a ProgressTimeSource,
ProgressStatuses a (IO Rational)) =>
a -> ProgressTimeSource
getETR a
po
a -> (ProgressStatus -> ProgressTimeSource) -> ProgressTimeSource
forall a b. ProgressStatuses a b => a -> (ProgressStatus -> b) -> b
withStatus a
po ((ProgressStatus -> ProgressTimeSource) -> ProgressTimeSource)
-> (ProgressStatus -> ProgressTimeSource) -> ProgressTimeSource
forall a b. (a -> b) -> a -> b
$ \ProgressStatus
status ->
do Integer
timenow <- ProgressStatus -> ProgressTimeSource
timeSource ProgressStatus
status
Integer -> ProgressTimeSource
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> ProgressTimeSource) -> Integer -> ProgressTimeSource
forall a b. (a -> b) -> a -> b
$ Integer
timenow Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
etr
defaultTimeSource :: ProgressTimeSource
defaultTimeSource :: ProgressTimeSource
defaultTimeSource = IO ClockTime
getClockTime IO ClockTime
-> (ClockTime -> ProgressTimeSource) -> ProgressTimeSource
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Integer -> ProgressTimeSource
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> ProgressTimeSource)
-> (ClockTime -> Integer) -> ClockTime -> ProgressTimeSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ClockTime -> Integer
forall a. Num a => ClockTime -> a
clockTimeToEpoch)
modStatus :: Progress -> (ProgressStatus -> ProgressStatus) -> IO ()
modStatus :: Progress -> (ProgressStatus -> ProgressStatus) -> IO ()
modStatus (Progress MVar ProgressRecord
mp) ProgressStatus -> ProgressStatus
func =
MVar ProgressRecord
-> (ProgressRecord -> IO ProgressRecord) -> IO ()
forall a. MVar a -> (a -> IO a) -> IO ()
modifyMVar_ MVar ProgressRecord
mp ProgressRecord -> IO ProgressRecord
modfunc
where modfunc :: ProgressRecord -> IO ProgressRecord
modfunc :: ProgressRecord -> IO ProgressRecord
modfunc ProgressRecord
oldpr =
do let newpr :: ProgressRecord
newpr = ProgressRecord
oldpr {status :: ProgressStatus
status = ProgressStatus -> ProgressStatus
func (ProgressRecord -> ProgressStatus
status ProgressRecord
oldpr)}
(ProgressCallback -> IO ()) -> [ProgressCallback] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\ProgressCallback
x -> ProgressCallback
x (ProgressRecord -> ProgressStatus
status ProgressRecord
oldpr) (ProgressRecord -> ProgressStatus
status ProgressRecord
newpr))
(ProgressRecord -> [ProgressCallback]
callbacks ProgressRecord
oldpr)
case (ProgressStatus -> Integer
completedUnits (ProgressStatus -> Integer)
-> (ProgressRecord -> ProgressStatus) -> ProgressRecord -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgressRecord -> ProgressStatus
status (ProgressRecord -> Integer) -> ProgressRecord -> Integer
forall a b. (a -> b) -> a -> b
$ ProgressRecord
newpr) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
-
(ProgressStatus -> Integer
completedUnits (ProgressStatus -> Integer)
-> (ProgressRecord -> ProgressStatus) -> ProgressRecord -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgressRecord -> ProgressStatus
status (ProgressRecord -> Integer) -> ProgressRecord -> Integer
forall a b. (a -> b) -> a -> b
$ ProgressRecord
oldpr) of
Integer
0 -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Integer
x -> ProgressRecord -> (Progress -> IO ()) -> IO ()
callParents ProgressRecord
newpr (\Progress
y -> Progress -> Integer -> IO ()
incrP' Progress
y Integer
x)
case (ProgressStatus -> Integer
totalUnits (ProgressStatus -> Integer)
-> (ProgressRecord -> ProgressStatus) -> ProgressRecord -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgressRecord -> ProgressStatus
status (ProgressRecord -> Integer) -> ProgressRecord -> Integer
forall a b. (a -> b) -> a -> b
$ ProgressRecord
newpr) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
-
(ProgressStatus -> Integer
totalUnits (ProgressStatus -> Integer)
-> (ProgressRecord -> ProgressStatus) -> ProgressRecord -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgressRecord -> ProgressStatus
status (ProgressRecord -> Integer) -> ProgressRecord -> Integer
forall a b. (a -> b) -> a -> b
$ ProgressRecord
oldpr) of
Integer
0 -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Integer
x -> ProgressRecord -> (Progress -> IO ()) -> IO ()
callParents ProgressRecord
newpr (\Progress
y -> Progress -> Integer -> IO ()
incrTotal Progress
y Integer
x)
ProgressRecord -> IO ProgressRecord
forall (m :: * -> *) a. Monad m => a -> m a
return ProgressRecord
newpr
callParents :: ProgressRecord -> (Progress -> IO ()) -> IO ()
callParents :: ProgressRecord -> (Progress -> IO ()) -> IO ()
callParents ProgressRecord
pr Progress -> IO ()
func = (Progress -> IO ()) -> [Progress] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Progress -> IO ()
func (ProgressRecord -> [Progress]
parents ProgressRecord
pr)