summaryrefslogtreecommitdiff
path: root/rtq.hs
diff options
context:
space:
mode:
Diffstat (limited to 'rtq.hs')
-rw-r--r--rtq.hs66
1 files changed, 39 insertions, 27 deletions
diff --git a/rtq.hs b/rtq.hs
index a47491a..83f97a6 100644
--- a/rtq.hs
+++ b/rtq.hs
@@ -1,46 +1,58 @@
1{-# LANGUAGE FlexibleContexts #-}
2{-# LANGUAGE ExplicitForAll #-}
3{-# LANGUAGE KindSignatures #-}
4
5import BasePrelude hiding ((.)) 1import BasePrelude hiding ((.))
6import RealTimeQueue 2import RealTimeQueue as Q
7import Control.Monad.IO.Class 3import Control.Monad.IO.Class
8import Control.Monad.State 4import Control.Monad.State
9import System.Clock 5import System.Clock
10 6
11data LoopState = LoopState { 7data LoopState = LoopState {
12 _queue :: Queue String 8 _queue :: Queue String,
9 _lastAction :: TimeSpec,
10 _beforeActing :: TimeSpec
13} 11}
14 12
13type Loop r = StateT LoopState IO r
14
15main :: IO () 15main :: IO ()
16main = void $ runStateT main' (LoopState createQueue) 16main = void $ runStateT (queueSomeStuff >> mainLoop) (LoopState createQueue (TimeSpec 0 0) (TimeSpec 0 0))
17 17 where
18main' :: StateT LoopState IO () 18 queueSomeStuff = do
19main' = do 19 now <- liftIO $ getTime Monotonic
20 queueAction $ scheduleEventIO (TimeSpec 1 0, "hello world") 20 modify $ \s -> s { _beforeActing = now, _lastAction = now }
21 queueAction $ scheduleEventIO (TimeSpec 2 0, "hello world") 21 forM_ [1,2,4,8,9,10,11,12] $ \i -> queueAction $ scheduleEventIO (TimeSpec i 0, "hello world " ++ show i)
22 queueAction $ scheduleEventIO (TimeSpec 3 0, "hello world") 22
23 queueAction $ scheduleEventIO (TimeSpec 4 0, "hello world") 23mainLoop :: Loop ()
24mainLoop = do
25 queueAction $ runScheduledIO tickTime runner
26 unlessEmptyQueue $ do
27 liftIO $ threadDelay' tickTime
24 mainLoop 28 mainLoop
25 29
26queueAction :: forall (m :: * -> *). MonadState LoopState m => (Queue String -> m (Queue String)) -> m () 30queueAction :: (Queue String -> Loop (Queue String)) -> Loop ()
27queueAction act = do 31queueAction act = do
28 q <- gets _queue 32 q <- gets _queue
29 act q >>= modify . const . LoopState 33 act q >>= \q' -> modify $ \s -> s { _queue = q' }
30 34
31tickTime :: TimeSpec 35tickTime :: TimeSpec
32tickTime = TimeSpec 0 15000 36tickTime = TimeSpec 0 1000
33 37
34threadDelay' :: TimeSpec -> IO () 38threadDelay' :: TimeSpec -> IO ()
35threadDelay' = threadDelay . fromIntegral . timeSpecAsNanoSecs 39threadDelay' = threadDelay . fromIntegral . timeSpecAsNanoSecs
36 40
37runner :: TimeSpec -> String -> StateT LoopState IO () 41timeSpecAsDouble :: TimeSpec -> Double
38runner delay str = liftIO $ do 42timeSpecAsDouble ts = x / (10^(9::Int)) where x = fromIntegral $ timeSpecAsNanoSecs ts
39 threadDelay' delay 43
40 putStrLn str 44runner :: (TimeSpec, String) -> Loop ()
41 45runner (delay, str) = do
42mainLoop :: StateT LoopState IO () 46 before <- gets _lastAction
43mainLoop = do 47 muchBefore <- gets _beforeActing
44 queueAction $ runScheduledIO tickTime runner 48 after <- liftIO $ do
45 liftIO $ threadDelay' tickTime 49 threadDelay' delay
46 mainLoop 50 now <- liftIO $ getTime Monotonic
51 print (now, str, timeSpecAsDouble $ now - before, timeSpecAsDouble $ now - muchBefore)
52 return now
53 modify $ \s -> s { _lastAction = after }
54
55unlessEmptyQueue :: Loop () -> Loop ()
56unlessEmptyQueue f = do
57 q <- gets _queue
58 unless (Q.null q) f