]> Git — Sourcephile - tmp/julm/arpeggigon.git/blob - src/RMCA/Layer/Board.hs
Code cleaning and seg fault tracking.
[tmp/julm/arpeggigon.git] / src / RMCA / Layer / Board.hs
1 {-# LANGUAGE Arrows #-}
2
3 module RMCA.Layer.Board ( boardRun
4 , BoardRun (..)
5 ) where
6
7 import qualified Data.IntMap as M
8 import Data.List ((\\))
9 import FRP.Yampa
10 import RMCA.Auxiliary
11 import RMCA.Layer.Layer
12 import RMCA.Semantics
13
14 data BoardRun = BoardStart | BoardStop deriving (Eq, Show)
15
16 singleBoard :: [PlayHead]
17 -> SF (Board, Layer, Event BeatNo) (Event ([PlayHead], [Note]))
18 singleBoard iPh = proc (board, Layer { relPitch = rp
19 , strength = s
20 }, ebno) ->
21 accumBy advanceHeads' (iPh,[]) -< ebno `tag` (board, fromEvent ebno, rp, s)
22 where advanceHeads' (ph,_) (board,bno,rp,s) = uncurry5 advanceHeads (board,bno,rp,s,ph)
23
24 boardSF :: SF (Board, Layer, Tempo, BoardRun) (Event ([PlayHead], [Note]))
25 boardSF = proc (board, l, t, br) -> do
26 ebno <- layerMetronome -< (t,l)
27 ess <- onChange -< br
28 boardSwitch [] -< ((board, l, ebno), ess `tag` (br, startHeads board))
29
30 boardSwitch :: [PlayHead]
31 -> SF ((Board, Layer,Event BeatNo), Event (BoardRun, [PlayHead]))
32 (Event ([PlayHead],[Note]))
33 boardSwitch rPh = dSwitch (singleBoard rPh *** (identity >>> notYet)) fnSwitch
34 where fnSwitch (BoardStart, iPh) = boardSwitch iPh
35 fnSwitch (BoardStop, _) = boardSwitch []
36
37 --------------------------------------------------------------------------------
38 -- Machinery to make parallel boards run
39 --------------------------------------------------------------------------------
40
41 routeBoard :: M.IntMap a -> M.IntMap sf -> M.IntMap (a,sf)
42 routeBoard = M.intersectionWith (,)
43
44 -- On the left are the disappearing signals, on the right the
45 -- appearing one.
46 lengthChange :: M.IntMap b -> SF (M.IntMap a, M.IntMap sf) (Event ([Int],[Int]))
47 lengthChange iSig = edgeBy diffSig ik <<^ M.keys <<^ fst
48 where ik = M.keys iSig
49 -- Old elements removed in nL are on the left, new elements added to
50 -- nL are on the right.
51 diffSig :: [Int] -> [Int] -> Maybe ([Int],[Int])
52 diffSig oL nL
53 | oL == nL = Nothing
54 | otherwise = Just (oL \\ nL, nL \\ oL)
55
56 boardRun' :: M.IntMap (SF (Board,Layer,Tempo,BoardRun)
57 (Event ([PlayHead],[Note])))
58 -> SF (M.IntMap (Board,Layer,Tempo,BoardRun))
59 (M.IntMap (Event ([PlayHead],[Note])))
60 boardRun' iSF = boardRun'' iSF (lengthChange iSF)
61 where boardRun'' iSF swSF = pSwitch routeBoard iSF swSF contSwitch
62 contSwitch contSig (oldSig, newSig) = boardRun'' newSF
63 (lengthChange newSF >>> notYet)
64 where newSF = foldr (\k m -> M.insert k boardSF m)
65 (foldr M.delete contSig oldSig) newSig
66
67 boardRun :: M.IntMap (Board,Layer,Tempo,BoardRun)
68 -> SF (M.IntMap (Board,Layer,Tempo,BoardRun))
69 (M.IntMap (Event ([PlayHead],[Note])))
70 boardRun iSig = boardRun' (iSig $> boardSF)