{-# LANGUAGE Arrows #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
module FRP.Rhine.Clock.Realtime.Millisecond where
import Data.Time.Clock
import Control.Concurrent (threadDelay)
import GHC.TypeLits (Nat, KnownNat)
import FRP.Rhine
import FRP.Rhine.Clock.Step
type Millisecond (n :: Nat) = RescaledClockS IO (Step n) UTCTime Bool
sleepClock :: KnownNat n => Millisecond n
sleepClock = sleepClock_ Step
where
sleepClock_ :: Step n -> Millisecond n
sleepClock_ cl = RescaledClockS cl $ const $ do
now <- getCurrentTime
return
( arrM_ (threadDelay (fromInteger $ stepsize cl * 1000) >> getCurrentTime)
*** arr (const False)
, now
)
waitClock :: KnownNat n => Millisecond n
waitClock = RescaledClockS Step $ \_ -> do
initTime <- getCurrentTime
let
runningClock = proc (n, ()) -> do
beforeSleep <- arrM_ getCurrentTime -< ()
let
diff :: Double
diff = realToFrac $ beforeSleep `diffUTCTime` initTime
remaining = fromInteger $ n * 1000 - round (diff * 1000000)
_ <- arrM threadDelay -< remaining
now <- arrM_ getCurrentTime -< ()
returnA -< (now, diff > 0)
return (runningClock, initTime)