1 {-# LANGUAGE MultiParamTypeClasses, ScopedTypeVariables, TupleSections #-}
5 import Control.Concurrent
6 import qualified Data.IntMap as M
7 import Data.ReactiveValue
10 import Graphics.UI.Gtk.Board.BoardLink
11 import Graphics.UI.Gtk.Layout.BackgroundContainer
15 import RMCA.Configuration
17 import RMCA.GUI.Buttons
18 import RMCA.GUI.LayerSettings
19 import RMCA.GUI.MainSettings
20 import RMCA.GUI.MultiBoard
21 import RMCA.GUI.NoteSettings
22 import RMCA.Layer.Board
23 import RMCA.Layer.Layer
25 import RMCA.Translator.Jack
29 ------------------------------------------------------------------------------
31 ------------------------------------------------------------------------------
35 mainBox <- hBoxNew False 10
36 set window [ windowTitle := "Reactogon"
37 , containerChild := mainBox
38 , containerBorderWidth := 10
42 settingsBox <- vBoxNew False 0
43 boxPackEnd mainBox settingsBox PackNatural 0
44 (globalSettingsBox, tempoRV) <- globalSettings
45 boxPackStart settingsBox globalSettingsBox PackNatural 0
46 globalSep <- hSeparatorNew
47 boxPackStart settingsBox globalSep PackNatural 0
50 playRV,stopRV,pauseRV,recordRV,
51 confSaveRV,confLoadRV,
52 addLayerRV,rmLayerRV) <- getButtons
53 boxPackEnd settingsBox buttonBox PackNatural 0
55 boardQueue <- newCBMVarRW mempty
56 (layerSettingsVBox, layerMCBMVar, instrMCBMVar) <- layerSettings boardQueue
57 boxPackStart settingsBox layerSettingsVBox PackNatural 0
58 laySep <- hSeparatorNew
59 boxPackStart settingsBox laySep PackNatural 0
61 (noteSettingsBox, guiCellMCBMVar) <- noteSettingsBox
62 (boardCont, boardMapRV, layerMapRV, phRVMapRV) <- createNotebook
64 layerMCBMVar guiCellMCBMVar
65 boxPackStart mainBox boardCont PackNatural 0
67 --handleSaveLoad tempoRV boardRV layerRV instrRV pieceArrRV confSaveRV confLoadRV
69 boardRunRV <- newCBMVarRW BoardStop
70 reactiveValueOnCanRead playRV $ reactiveValueWrite boardRunRV BoardStart
71 reactiveValueOnCanRead stopRV $ reactiveValueWrite boardRunRV BoardStop
72 boardMap <- reactiveValueRead boardMapRV
73 layerMap <- reactiveValueRead layerMapRV
74 tempo <- reactiveValueRead tempoRV
75 let tempoRV' = liftR2 (\bool t -> t * fromEnum (not bool)) pauseRV tempoRV
76 inRV :: ReactiveFieldRead IO (M.IntMap (Board,Layer,Tempo,BoardRun))
77 inRV = liftR4 (\bm lm t br -> M.map (\(b,l) -> (b,l,t,br)) $
78 M.intersectionWith (,) bm lm)
79 boardMapRV layerMapRV tempoRV' boardRunRV
80 initSF <- reactiveValueRead inRV
81 (inBoard, outBoard) <- yampaReactiveDual initSF (boardRun initSF)
82 --reactiveValueOnCanRead inRV (reactiveValueRead inRV >>= print . M.keys)
84 reactiveValueOnCanRead outBoard $ do
85 out <- reactiveValueRead outBoard
87 phRVMap <- reactiveValueRead phRVMapRV
89 let eventsMap = M.filter isEvent out
91 fromMaybeM_ $ fmap (\ph -> reactiveValueWrite ph val) $
93 noteMap = M.map (eventToList . snd . splitE) out
94 sequence_ $ M.mapWithKey writePh $
95 M.map (fst . fromEvent) $ M.filter isEvent out
96 reactiveValueAppend boardQueue $ M.map (,[]) noteMap
100 reactiveValueRead (liftR (event mempty (,[]) <<< snd <<< splitE) outBoard) >>=
101 reactiveValueAppend boardQueue-}
102 -- This needs to be set last otherwise phRV is written to, so
103 -- inBoard is written to and the notes don't get played. There
104 -- supposedly is no guaranty of order but apparently there is…
105 putStrLn "Board started."
107 forkIO $ jackSetup boardQueue
110 ------------------------------------------------------------
112 boxPackStart settingsBox noteSettingsBox PackNatural 10
113 onDestroy window mainQuit