]> Git — Sourcephile - tmp/julm/arpeggigon.git/blob - src/RMCA/Layer/Board.hs
repeatCount works from the SF.
[tmp/julm/arpeggigon.git] / src / RMCA / Layer / Board.hs
1 {-# LANGUAGE Arrows #-}
2
3 module RMCA.Layer.Board where
4
5 import qualified Data.IntMap as M
6 import Data.List ((\\))
7 import FRP.Yampa
8 import RMCA.Auxiliary
9 import RMCA.Global.Clock
10 import RMCA.Layer.LayerConf
11 import RMCA.Semantics
12
13 import Debug.Trace
14
15 data RunStatus = Running | Stopped
16
17 layerMetronome :: StaticLayerConf
18 -> SF (Event AbsBeat, DynLayerConf) (Event BeatNo)
19 layerMetronome StaticLayerConf { beatsPerBar = bpb
20 } =
21 proc (eb, DynLayerConf { layerBeat = r
22 }) -> do
23 ewbno <- accumFilter (\_ (ab,r) -> ((),selectBeat (ab,r))) () -< (,r) <$> eb
24 accumBy (flip nextBeatNo) 0 -< ewbno `tag` bpb
25 where selectBeat (absBeat, layBeat) =
26 maybeIf ((absBeat - 1) `mod`
27 floor (fromIntegral maxAbsBeat * layBeat) == 0)
28
29 automaton :: [PlayHead]
30 -> SF (Board, DynLayerConf, Event BeatNo)
31 (Event [Note], [PlayHead])
32 automaton iphs = proc (b, DynLayerConf { relPitch = rp
33 , strength = s
34 }, ebno) -> do
35 enphs <- accumBy advanceHeads' (iphs,[])
36 -< ebno `tag` (b, fromEvent ebno, rp, s)
37 (ephs,en) <- arr splitE -< enphs
38 phs <- hold iphs -< ephs
39 returnA -< (en, phs)
40 where advanceHeads' (ph,_) (board,bno,rp,s) = advanceHeads board bno rp s ph
41
42
43 layer :: SF (Event AbsBeat, Board, LayerConf, Event RunStatus)
44 (Event [Note], [PlayHead])
45 layer = layerStopped
46 where switchStatus (rs, slc, iphs) = case rs of
47 Stopped -> layerStopped
48 Running -> layerRunning slc iphs
49
50 layerStopped = switch lsAux switchStatus
51
52 layerRunning slc iphs = switch (lrAux slc iphs) switchStatus
53
54 lsAux = proc (_, b, (slc,_,_), ers) -> do
55 en <- never -< ()
56 phs <- constant [] -< ()
57 e <- notYet -< fmap (\rs -> (rs, slc, startHeads b)) ers
58 returnA -< ((en,phs),e)
59
60 lrAux slc iphs = proc (eab, b, (slc',dlc,_), ers) -> do
61 ebno <- layerMetronome slc -< (eab, dlc)
62 enphs@(_,phs) <- automaton iphs -< (b, dlc, traceShow ebno ebno)
63 r <- (case let a = repeatCount slc in traceShow a a of
64 Nothing -> never
65 Just n -> countTo (1 + n * beatsPerBar slc)) -< ebno
66 let ers' = ers `lMerge` (r `tag` Running)
67 ophs <- iPre iphs -< phs
68 e <- notYet -< fmap (\rs -> (rs, slc', ophs ++ startHeads b)) ers'
69 returnA -< (enphs,e)
70
71 layers :: M.IntMap a
72 -> SF (Tempo, Event RunStatus,
73 M.IntMap (Board,LayerConf,Event RunStatus))
74 (M.IntMap (Event [Note], [PlayHead]))
75 layers imap = proc (t,erun,map) -> do
76 elc <- edgeBy diffSig (M.keys imap) -< M.keys map
77 let e = fmap switchCol elc
78 newMetronome Running = metronome
79 newMetronome Stopped = never
80 eabs <- rSwitch metronome -< (t, newMetronome <$> erun)
81 rpSwitch routing (imap $> layer) -< ((eabs,erun,map),e)
82 where routing (eabs,erun,map) sfs = M.intersectionWith (,)
83 (fmap (\(b,l,er) -> (eabs,b,l,erun `lMerge` er)) map) sfs
84
85 diffSig :: [Int] -> [Int] -> Maybe ([Int],[Int])
86 diffSig oL nL
87 | oL == nL = Nothing
88 | otherwise = Just (oL \\ nL, nL \\ oL)
89
90 switchCol (oldSig,newSig) col =
91 foldr (\k m -> M.insert k layer m)
92 (foldr M.delete col oldSig) newSig