1 {-# LANGUAGE FlexibleContexts #-}
3 -- Contains all the information and functions necessary to run a Jack
4 -- port and exchange information through reactive values and Yampa.
5 module RMCA.Translator.Jack ( jackSetup
8 import qualified Control.Monad.Exception.Synchronous as Sync
9 import qualified Control.Monad.Trans.Class as Trans
10 import qualified Data.Bifunctor as BF
12 import Data.ReactiveValue
13 import qualified Foreign.C.Error as E
15 import RMCA.Auxiliary.RV
17 import RMCA.Translator.Filter
18 import RMCA.Translator.Message
19 import RMCA.Translator.RV
20 import RMCA.Translator.Translator
21 import qualified Sound.JACK as Jack
22 import qualified Sound.JACK.MIDI as JMIDI
31 outPortName = "output"
33 -- Starts a default client with an input and an output port. Doesn't
34 -- do anything as such.
35 jackSetup :: ( ReactiveValueRead tempo LTempo IO
36 , ReactiveValueRead channel Int IO
37 , ReactiveValueReadWrite board ([Note],[Message]) IO) =>
42 jackSetup tempoRV chanRV boardInRV = Jack.handleExceptions $ do
43 toProcessRV <- Trans.lift $ toProcess <$> newCBMVar []
44 Jack.withClientDefault rmcaName $ \client ->
45 Jack.withPort client outPortName $ \output ->
46 Jack.withPort client inPortName $ \input ->
47 Jack.withProcess client (jackCallBack client input output
48 toProcessRV tempoRV chanRV boardInRV) $
49 Jack.withActivation client $ Trans.lift $ do
50 putStrLn $ "Started " ++ rmcaName ++ " JACK client."
54 -- Loop that does nothing except setting up a callback function
55 -- (called when Jack is ready to take new inputs).
56 jackRun :: (JExc.ThrowsErrno e) =>
58 -> (Jack.NFrames -> Sync.ExceptionalT E.Errno IO ())
59 -> Sync.ExceptionalT e IO ()
60 jackRun client callback =
61 Jack.withProcess client callback $ do
62 Trans.lift $ putStrLn $ "Startedbbb " ++ rmcaName
63 Trans.lift $ Jack.waitForBreak
68 -- The callback function. It pumps value out of the input port, mix
69 -- them with value coming from the machine itself and stuff them into
70 -- the output port. When this function is not running, events are
72 jackCallBack :: ( ReactiveValueReadWrite toProcess [(Frames, RawMessage)] IO
73 , ReactiveValueRead tempo LTempo IO
74 , ReactiveValueRead channel Int IO
75 , ReactiveValueReadWrite board ([Note],[Message]) IO) =>
77 -> JMIDI.Port Jack.Input
78 -> JMIDI.Port Jack.Output
84 -> Sync.ExceptionalT E.Errno IO ()
85 jackCallBack client input output toProcessRV tempoRV chanRV outBoard
86 nframes@(Jack.NFrames nframesInt') = do
87 let inMIDIRV = inMIDIEvent input nframes
88 outMIDIRV = outMIDIEvent output nframes
89 nframesInt = fromIntegral nframesInt' :: Int
90 -- This gets the sample rate of the client and the last frame number
91 -- it processed. We then use it to calculate the current absolute time
92 sr <- Trans.lift $ Jack.getSampleRate client
93 --(Jack.NFrames lframeInt) <- Trans.lift $ Jack.lastFrameTime client
94 --Trans.lift (reactiveValueRead inMIDIRV >>= (print . map (fst)))
95 -- We write the content of the input buffer to the input of a
96 -- translation signal function.
97 -- /!\ Should maybe be moved elsewhere
98 (inRaw, outPure) <- Trans.lift $ yampaReactiveDual [] readMessages
99 Trans.lift (inMIDIRV =:> inRaw)
100 tempo <- Trans.lift $ reactiveValueRead tempoRV
101 chan <- Trans.lift $ reactiveValueRead chanRV
102 (notes,ctrl) <- Trans.lift $ reactiveValueRead outBoard
103 Trans.lift $ emptyRW outBoard
104 let boardIn = (zip (repeat 0) notes, zip (repeat 0) ctrl, [])
105 outMIDI <- Trans.lift $ reactiveValueRead outPure
106 -- We translate all signals to be sent into low level signals and
107 -- write them to the output buffer.
108 (inPure, outRaw) <- Trans.lift $ yampaReactiveDual
109 (defaultTempo, sr, chan, ([],[],[])) gatherMessages
110 -- This should all go in its own IO action
112 reactiveValueWrite inPure (tempo, sr, chan, boardIn `mappend` outMIDI)
113 reactiveValueRead outRaw >>= reactiveValueAppend toProcessRV
114 --map fst <$> reactiveValueRead toProcessRV >>= print . ("toProcess " ++) . show
115 (go, old') <- schedule nframesInt <$> reactiveValueRead toProcessRV
116 let old = map (BF.first (+ (- nframesInt))) old'
117 reactiveValueWrite outMIDIRV go
118 reactiveValueWrite toProcessRV old