]> Git — Sourcephile - tmp/julm/arpeggigon.git/blob - src/RMCA/Global/Clock.hs
Minor refactoring.
[tmp/julm/arpeggigon.git] / src / RMCA / Global / Clock.hs
1 module RMCA.Global.Clock where
2
3 import Control.Concurrent
4 import Control.Monad
5 import Data.CBMVar
6 import Data.ReactiveValue
7 import FRP.Yampa
8 import RMCA.Auxiliary
9 import RMCA.Semantics
10
11 -- The initial value is arbitrary but never appears because the switch
12 -- is immediate.
13 metronome :: SF Tempo (Event Beat)
14 metronome = switch (repeatedly (tempoToQNoteIvl 120) ()
15 &&&
16 onChange') metronome'
17 where metronome' :: Tempo -> SF Tempo (Event Beat)
18 metronome' t = switch (repeatedly (tempoToQNoteIvl t) ()
19 &&&
20 onChange) metronome'
21
22 -- Tempo is the number of quarter notes per minute.
23 tempoToQNoteIvl :: Tempo -> DTime
24 tempoToQNoteIvl = (15/) . fromIntegral
25
26 type TickingClock = (CBMVar (), ThreadId)
27
28 -- Make a clock that will execute any IO when it updates.
29 mkClockGeneric :: IO () -> DTime -> IO TickingClock
30 mkClockGeneric io d = do
31 n <- newCBMVar ()
32 tid <- forkIO $ forever $ do
33 threadDelay dInt
34 modifyCBMVar n return
35 io
36 return (n, tid)
37 where dInt = floor $ d * 1000
38
39 -- Ticking clock in the IO monad, sending callbacks every t milliseconds.
40 mkClock :: DTime -> IO TickingClock
41 mkClock = mkClockGeneric (return ())
42
43 -- For debugging purposes.
44 mkClockDebug :: DTime -> IO TickingClock
45 mkClockDebug = mkClockGeneric (putStrLn "Ping !")
46
47 clockRV :: TickingClock -> ReactiveFieldRead IO ThreadId
48 clockRV (mvar, tid) = ReactiveFieldRead (return tid)
49 (installCallbackCBMVar mvar)
50
51 mkClockRV :: DTime -> IO (ReactiveFieldRead IO ThreadId)
52 mkClockRV d = clockRV <$> mkClock d
53
54 stopClock :: TickingClock -> IO ()
55 stopClock (_,t) = killThread t