mirror of https://github.com/voidlizard/hbs2
wip, minor refactoring
This commit is contained in:
parent
28590c6936
commit
5b052e8a56
|
@ -134,6 +134,7 @@ library
|
||||||
, microlens-platform
|
, microlens-platform
|
||||||
, mtl
|
, mtl
|
||||||
, murmur-hash
|
, murmur-hash
|
||||||
|
, time
|
||||||
, network
|
, network
|
||||||
, network-multicast
|
, network-multicast
|
||||||
, network-simple
|
, network-simple
|
||||||
|
|
|
@ -1,4 +1,3 @@
|
||||||
{-# Language FunctionalDependencies #-}
|
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
module HBS2.Clock
|
module HBS2.Clock
|
||||||
( module HBS2.Clock
|
( module HBS2.Clock
|
||||||
|
@ -12,8 +11,9 @@ import Data.Int (Int64)
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
import Prettyprinter
|
import Prettyprinter
|
||||||
import System.Clock
|
import System.Clock
|
||||||
|
import Data.Time.Clock
|
||||||
|
|
||||||
data TimeoutKind = MilliSeconds | Seconds | Minutes
|
data TimeoutKind = MilliSeconds | Seconds | Minutes | NomDiffTime | TS
|
||||||
|
|
||||||
data family Timeout ( a :: TimeoutKind )
|
data family Timeout ( a :: TimeoutKind )
|
||||||
|
|
||||||
|
@ -25,7 +25,6 @@ newtype Delay a = Delay a
|
||||||
deriving newtype (Eq,Show,Pretty)
|
deriving newtype (Eq,Show,Pretty)
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
class IsTimeout a where
|
class IsTimeout a where
|
||||||
toNanoSeconds :: Timeout a -> Int64
|
toNanoSeconds :: Timeout a -> Int64
|
||||||
|
|
||||||
|
@ -56,6 +55,20 @@ newtype instance Timeout 'Minutes =
|
||||||
TimeoutMin (Fixed E9)
|
TimeoutMin (Fixed E9)
|
||||||
deriving newtype (Eq,Ord,Num,Real,Fractional,Show,Pretty)
|
deriving newtype (Eq,Ord,Num,Real,Fractional,Show,Pretty)
|
||||||
|
|
||||||
|
newtype instance Timeout 'NomDiffTime =
|
||||||
|
TimeoutNDT NominalDiffTime
|
||||||
|
deriving newtype (Eq,Ord,Num,Real,Fractional,Show,Pretty)
|
||||||
|
|
||||||
|
newtype instance Timeout 'TS =
|
||||||
|
TimeoutTS TimeSpec
|
||||||
|
deriving newtype (Eq,Ord,Num,Real,Show,Pretty)
|
||||||
|
|
||||||
|
instance Pretty NominalDiffTime where
|
||||||
|
pretty = viaShow
|
||||||
|
|
||||||
|
instance Pretty TimeSpec where
|
||||||
|
pretty = viaShow
|
||||||
|
|
||||||
instance IsTimeout 'MilliSeconds where
|
instance IsTimeout 'MilliSeconds where
|
||||||
toNanoSeconds (TimeoutMSec x) = round (x * 1e6)
|
toNanoSeconds (TimeoutMSec x) = round (x * 1e6)
|
||||||
|
|
||||||
|
@ -65,6 +78,12 @@ instance IsTimeout 'Seconds where
|
||||||
instance IsTimeout 'Minutes where
|
instance IsTimeout 'Minutes where
|
||||||
toNanoSeconds (TimeoutMin x) = round (x * 60 * 1e9)
|
toNanoSeconds (TimeoutMin x) = round (x * 60 * 1e9)
|
||||||
|
|
||||||
|
instance IsTimeout 'NomDiffTime where
|
||||||
|
toNanoSeconds (TimeoutNDT t) = round (realToFrac (nominalDiffTimeToSeconds t) * 1e9)
|
||||||
|
|
||||||
|
instance IsTimeout 'TS where
|
||||||
|
toNanoSeconds (TimeoutTS s) = fromIntegral $ toNanoSecs s
|
||||||
|
|
||||||
class Expires a where
|
class Expires a where
|
||||||
expiresIn :: Proxy a -> Maybe (Timeout 'Seconds)
|
expiresIn :: Proxy a -> Maybe (Timeout 'Seconds)
|
||||||
|
|
||||||
|
|
|
@ -417,7 +417,7 @@ polling :: forall a m . (MonadIO m, Hashable a)
|
||||||
|
|
||||||
polling o listEntries action = do
|
polling o listEntries action = do
|
||||||
|
|
||||||
pause (TimeoutSec (nominalDiffTimeToSeconds (waitBefore o)))
|
pause (TimeoutNDT (waitBefore o))
|
||||||
|
|
||||||
now0 <- getTimeCoarse
|
now0 <- getTimeCoarse
|
||||||
refs0 <- listEntries <&> fmap (set _2 now0) <&> HashMap.fromList
|
refs0 <- listEntries <&> fmap (set _2 now0) <&> HashMap.fromList
|
||||||
|
@ -426,7 +426,7 @@ polling o listEntries action = do
|
||||||
now <- getTimeCoarse
|
now <- getTimeCoarse
|
||||||
refs <- listEntries <&> HashMap.fromList
|
refs <- listEntries <&> HashMap.fromList
|
||||||
let mon' = mon `HashMap.union`
|
let mon' = mon `HashMap.union`
|
||||||
HashMap.fromList [ (e, now + fromNanoSecs (round (realToFrac (nominalDiffTimeToSeconds t) * 1e9)))
|
HashMap.fromList [ (e, now + toTimeSpec (TimeoutNDT t))
|
||||||
| (e, t) <- HashMap.toList refs
|
| (e, t) <- HashMap.toList refs
|
||||||
]
|
]
|
||||||
|
|
||||||
|
@ -440,11 +440,11 @@ polling o listEntries action = do
|
||||||
next (HashMap.delete r mon')
|
next (HashMap.delete r mon')
|
||||||
|
|
||||||
Just (Entry t _, _) | otherwise -> do
|
Just (Entry t _, _) | otherwise -> do
|
||||||
pause @'Seconds $ fromInteger $ round $ realToFrac (toNanoSecs (t - now)) / 1e9
|
pause (TimeoutTS (t - now))
|
||||||
next mon'
|
next mon'
|
||||||
|
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
pause (TimeoutSec (nominalDiffTimeToSeconds (waitOnEmpty o)))
|
pause (TimeoutNDT (waitOnEmpty o))
|
||||||
next mon'
|
next mon'
|
||||||
|
|
||||||
) refs0
|
) refs0
|
||||||
|
|
Loading…
Reference in New Issue