--- /dev/null
+import FRP.Yampa
+import Hails.Yampa
+import Reactogon.Semantics
+import Reactogon.Translator.Message
+import Reactogon.Translator.Translator
+
+-- The whole system is a single SF getting new messages, transforming
+-- them and adding some more.
+reactogon :: SF [(Frames, RawMessage)] [(Frames, RawMessage)]
+reactogon = undefined
+
+main :: IO ()
+main = do
+ (inp, out) <- yampaReactiveDual [] reactogon
+ return ()
-- list are sorted.
--
-- /!\ The time is relative. A preprocessing operation removing all
--- events to soon to be happening and shifting them is necessary.
+-- events too soon to be happening and shifting them is necessary.
schedule :: (Eq a) =>
SampleRate
-> NFrames
module Reactogon.Translator.Message where
import Reactogon.Semantics
+import qualified Sound.JACK as Jack
import qualified Sound.MIDI.Message as Message
import qualified Sound.MIDI.Message.Channel as Channel
import qualified Sound.MIDI.Message.Channel.Voice as Voice
type ControllerIdx = Voice.Controller
+type Frames = Jack.NFrames
+
-- Each channel is linked to a particular translation signal function
-- itself linked to a particular layer. Therefore we will dispose of
-- the channel number as soon as possible.
import qualified Data.Bifunctor as BF
import Data.Maybe
+import FRP.Yampa
import Reactogon.Semantics
import Reactogon.Translator.Message
-- TEMPORARY
-data Control
+data Controller = Lol
--
sortRawMessages :: [RawMessage] -> ([Message], [RawMessage])
-}
-- Note messages are converted to PlayHeads
-sortMessages :: SF ([Message], [Message]) ([Note], [Control])
+sortMessages :: SF ([Message], [Message]) ([Note], [Controller])
sortMessages = proc (notes, ctrl) -> do
- notes' <- convertNotes -< notes
- ctrl' <- convertControl -< ctrl
+ notes' <- arr $ map convertNotes -< notes
+ ctrl' <- arr $ map convertControl -< ctrl
returnA -< (notes', ctrl')
-gatherMessages :: ([Note], [Control], [RawMessage]) -> [Message]
+-- /!\ Unsafe function that shouldn't be exported.
+convertNotes :: Message -> Note
+convertNotes = undefined
+
+-- /!\ Unsafe function that shouldn't be exported.
+convertControl :: Message -> Controller
+convertControl _ = Lol
+
+gatherMessages :: ([Note], [Controller], [RawMessage]) -> [Message]
gatherMessages ([], [], []) = []
gatherMessages _ = undefined
-readMessages :: SF ([RawMessage]) ([Note], [Control], [RawMessages])
+readMessages :: SF ([RawMessage]) ([Note], [Controller], [RawMessage])
readMessages = undefined
module Reactogon.Translator.Translator where
+import FRP.Yampa
import Reactogon.Semantics
import Reactogon.Translator.Message
+import Reactogon.Translator.SortMessage
-- Takes a stream of raw messages and translates them by type.
-fromRaw :: SF RawMessage (Note, SystemMessage, RawMessage)
+fromRaw :: SF RawMessage (Note, Controller, RawMessage)
fromRaw = undefined
-- Takes a stream of high level messages and translates them by type.
-toRaw :: SF (Note, SystemMessage, RawMessage) RawMessage
+toRaw :: SF (Note, Controller, RawMessage) RawMessage
toRaw = undefined