]> Git — Sourcephile - tmp/julm/arpeggigon.git/blob - RCMA/Translator/Jack.hs
Jack implementation should remain untouched before basic layer is done.
[tmp/julm/arpeggigon.git] / RCMA / Translator / Jack.hs
1 {-# LANGUAGE Arrows #-}
2
3 -- Contains all the information and functions necessary to run a Jack
4 -- port and exchange information through reactive values and Yampa.
5 module RCMA.Translator.Jack ( jackSetup
6 ) where
7
8 import Control.Applicative ((<**>))
9 import qualified Control.Monad.Exception.Synchronous as Sync
10 import qualified Control.Monad.Trans.Class as Trans
11 import qualified Data.Bifunctor as BF
12 import Data.CBMVar
13 import qualified Data.EventList.Absolute.TimeBody as EventListAbs
14 import Data.ReactiveValue
15 import qualified Foreign.C.Error as E
16 import Hails.Yampa
17 import RCMA.Semantics
18 import RCMA.Translator.Filter
19 import RCMA.Translator.Message
20 import RCMA.Translator.RV
21 import RCMA.Translator.Translator
22 import qualified Sound.JACK as Jack
23 import qualified Sound.JACK.Exception as JExc
24 import qualified Sound.JACK.MIDI as JMIDI
25
26 rcmaName :: String
27 rcmaName = "RCMA"
28
29 inPortName :: String
30 inPortName = "input"
31
32 outPortName :: String
33 outPortName = "output"
34
35 -- Starts a default client with an input and an output port. Doesn't
36 -- do anything as such.
37 jackSetup :: ReactiveFieldRead IO (LTempo, Int, [(Frames, RawMessage)])
38 -> IO ()
39 jackSetup boardInRV = Jack.handleExceptions $ do
40 toProcessRV <- Trans.lift $ toProcess <$> newCBMVar []
41 Jack.withClientDefault rcmaName $ \client ->
42 Jack.withPort client outPortName $ \output ->
43 Jack.withPort client inPortName $ \input ->
44 jackRun client (jackCallBack client input output toProcessRV boardInRV)
45
46 -- Loop that does nothing except setting up a callback function
47 -- (called when Jack is ready to take new inputs).
48 jackRun :: (JExc.ThrowsErrno e) =>
49 Jack.Client
50 -> (Jack.NFrames -> Sync.ExceptionalT E.Errno IO ())
51 -> Sync.ExceptionalT e IO ()
52 jackRun client callback =
53 Jack.withProcess client callback $ do
54 Trans.lift $ putStrLn $ "Started " ++ rcmaName
55 Trans.lift $ Jack.waitForBreak
56
57 defaultTempo :: Tempo
58 defaultTempo = 96
59
60 -- The callback function. It pumps value out of the input port, mix
61 -- them with value coming from the machine itself and stuff them into
62 -- the output port. When this function is not running, events are
63 -- processed.
64 jackCallBack :: Jack.Client
65 -> JMIDI.Port Jack.Input
66 -> JMIDI.Port Jack.Output
67 -> ReactiveFieldReadWrite IO [(Frames, RawMessage)]
68 -> ReactiveFieldRead IO (LTempo, Int, [(Frames, RawMessage)])
69 -> Jack.NFrames
70 -> Sync.ExceptionalT E.Errno IO ()
71 jackCallBack client input output toProcessRV boardInRV
72 nframes@(Jack.NFrames nframesInt') = do
73 let inMIDIRV = inMIDIEvent input nframes
74 outMIDIRV = outMIDIEvent output nframes
75 nframesInt = fromIntegral nframesInt' :: Int
76 -- This gets the sample rate of the client and the last frame number
77 -- it processed. We then use it to calculate the current absolute time
78 sr <- Trans.lift $ Jack.getSampleRate client
79 (Jack.NFrames lframeInt) <- Trans.lift $ Jack.lastFrameTime client
80 -- We write the content of the input buffer to the input of a
81 -- translation signal function.
82 -- /!\ Should be moved elsewhere
83 (inRaw, outPure) <- Trans.lift $ yampaReactiveDual [] readMessages
84 Trans.lift (inMIDIRV =:> inRaw)
85 (tempo, chan, boardIn') <- Trans.lift $ reactiveValueRead boardInRV
86 let boardIn = ([],[],boardIn')
87 outMIDI <- Trans.lift $ reactiveValueRead outPure
88 -- We translate all signals to be sent into low level signals and
89 -- write them to the output buffer.
90 (inPure, outRaw) <- Trans.lift $ yampaReactiveDual
91 (defaultTempo, sr, chan, ([],[],[])) gatherMessages
92 -- This should all go in its own IO action
93 Trans.lift $ reactiveValueWrite inPure
94 (tempo, sr, chan, (boardIn `mappend` outMIDI))
95 Trans.lift (reactiveValueRead outRaw <**>
96 (mappend <$> reactiveValueRead toProcessRV) >>=
97 reactiveValueWrite toProcessRV)
98 Trans.lift $ do
99 (go, old') <- schedule nframesInt <$> reactiveValueRead toProcessRV
100 let old = map (BF.first (+ (- nframesInt))) old'
101 reactiveValueWrite outMIDIRV go
102 reactiveValueWrite toProcessRV old
103 --------------
104 return ()