1 {-# LANGUAGE FlexibleContexts, MultiParamTypeClasses, ScopedTypeVariables,
4 module RMCA.GUI.NoteSettings where
11 import Data.ReactiveValue
14 import Graphics.UI.Gtk hiding (Action)
15 import Graphics.UI.Gtk.Reactive
21 setNAttr :: NoteAttr -> Action -> Action
22 setNAttr _ Inert = Inert
23 setNAttr _ Absorb = Absorb
24 setNAttr na (Stop _) = Stop na
25 setNAttr na (ChDir b _ dir) = ChDir b na dir
26 setNAttr na (Split _) = Split na
28 getNAttr :: Action -> Maybe NoteAttr
29 getNAttr Inert = Nothing
30 getNAttr Absorb = Nothing
31 getNAttr (Stop na) = Just na
32 getNAttr (ChDir _ na _) = Just na
33 getNAttr (Split na) = Just na
35 symbolString :: [(Duration,String)]
36 symbolString = map (\(_,y,z) -> (z,y)) noteSymbList
38 noteList :: [(String,Duration)]
39 noteList = map (\(x,_,y) -> (x,y)) noteSymbList
41 noteSymbList :: [(String, String, Duration)]
42 noteSymbList = sortBy (comparing (\(_,_,x) -> x))
43 [ ("♩", "Quarter note", 1 % 4)
44 , ("♪", "Eighth note ", 1 % 8)
45 , ("𝅗𝅥", "Half note", 1 % 2)
46 , ("𝅘𝅥𝅯", "Sixteenth note", 1 % 16)
47 , ("𝅝", "Whole note", 1)
50 comboBoxIndexRV :: (ComboBoxClass box) =>
51 box -> ReactiveFieldReadWrite IO Int
52 comboBoxIndexRV box = ReactiveFieldReadWrite setter getter notifier
53 where getter = comboBoxGetActive box
54 setter = comboBoxSetActive box
55 notifier = void . on box changed
57 noteSettingsBox :: IO (VBox, MCBMVar GUICell)
59 pieceBox <- vBoxNew False 10
60 naBox <- vBoxNew False 10
61 boxPackStart pieceBox naBox PackNatural 10
64 artCombo <- comboBoxNewText
65 artIndex <- mapM (\art -> do i <- comboBoxAppendText artCombo
66 (fromString $ show art)
67 return (art,i)) [NoAccent ..]
68 comboBoxSetActive artCombo 0
69 boxPackStart naBox artCombo PackNatural 10
71 fromMaybe (error "In indexToArt: failed \
72 \to find the selected \
73 \articulation.") $ lookup i $ map swap artIndex
74 artToIndex a = fromMaybe (error "In artToIndex: failed \
75 \to find the correct index \
77 \articulation.") $ lookup a artIndex
78 artComboRV = bijection (indexToArt,artToIndex) `liftRW`
79 comboBoxIndexRV artCombo
82 slideCombo <- comboBoxNewText
83 slideIndex <- mapM (\sli -> do i <- comboBoxAppendText slideCombo
84 (fromString $ show sli)
85 return (sli,i)) [NoSlide ..]
86 comboBoxSetActive slideCombo 0
87 boxPackStart naBox slideCombo PackNatural 10
89 fromMaybe (error "In indexToSlide: failed \
90 \to find the correct slide \
92 \index.") $ lookup i $ map swap slideIndex
94 fromMaybe (error "In slideToIndex: failed \
97 \for the slide.") $ lookup s slideIndex
98 slideComboRV = bijection (indexToSlide,slideToIndex) `liftRW`
99 comboBoxIndexRV slideCombo
102 noteDurBox <- hBoxNew False 10
103 noteDurCombo <- comboBoxNewText
104 noteDurIndex <- mapM (\(str,dur) -> do i <- comboBoxAppendText noteDurCombo
106 return (dur,i)) noteList
107 comboBoxSetActive noteDurCombo 0
109 fromMaybe (error "In indexToDur: failed \
110 \to find the correct \
112 \selected index.") $ lookup i $ map swap noteDurIndex
114 fromMaybe (error "In durToIndex: \
117 \for the duration.") $ lookup d noteDurIndex
118 noteDurRV = bijection (indexToDur, durToIndex) `liftRW`
119 comboBoxIndexRV noteDurCombo
120 noteDurLabel <- labelNew =<< (`lookup` symbolString) <$> reactiveValueRead noteDurRV
121 let noteDurLabelRV = labelTextReactive noteDurLabel
122 boxPackStart naBox noteDurBox PackNatural 10
123 boxPackStart noteDurBox noteDurCombo PackNatural 10
124 boxPackStart noteDurBox noteDurLabel PackNatural 10
127 rCountAdj <- adjustmentNew 1 0 100 1 1 0
128 rCount <- spinButtonNew rCountAdj 1 0
129 boxPackStart pieceBox rCount PackNatural 10
130 let rCountRV = spinButtonValueIntReactive rCount
133 -- Carries the index of the tile to display and what to display.
134 setRV <- newMCBMVar inertCell
136 reactiveValueOnCanRead noteDurRV $ do
137 nDur <- reactiveValueRead noteDurRV
138 oCell <- reactiveValueRead setRV
139 let nCa :: Maybe NoteAttr
140 nCa = (\na -> na { naDur = nDur }) <$> getNAttr (cellAction oCell)
142 nCell = if isJust nCa
143 then oCell { cellAction =
144 setNAttr (fromJust nCa) (cellAction oCell) }
146 reactiveValueWriteOnNotEq setRV nCell
147 fromMaybeM_ $ reactiveValueWrite noteDurLabelRV <$> lookup nDur symbolString
150 reactiveValueOnCanRead rCountRV $ do
151 nRCount <- reactiveValueRead rCountRV
152 oCell <- reactiveValueRead setRV
153 let nCell = oCell { repeatCount = nRCount }
154 reactiveValueWrite setRV nCell
156 reactiveValueOnCanRead slideComboRV $ do
157 nSlide <- reactiveValueRead slideComboRV
158 oCell <- reactiveValueRead setRV
159 let nCa :: Maybe NoteAttr
160 nCa = (\na -> na { naOrn = (naOrn na) { ornSlide = nSlide } }) <$>
161 getNAttr (cellAction oCell)
163 nCell = if isJust nCa
164 then oCell { cellAction =
165 setNAttr (fromJust nCa) (cellAction oCell)
168 reactiveValueWrite setRV nCell
170 reactiveValueOnCanRead artComboRV $ do
171 nArt <- reactiveValueRead artComboRV
172 oCell <- reactiveValueRead setRV
173 let nCa :: Maybe NoteAttr
174 nCa = (\na -> na { naArt = nArt }) <$> getNAttr (cellAction oCell)
176 nCell = if isJust nCa
177 then oCell { cellAction =
178 setNAttr (fromJust nCa) (cellAction oCell) }
180 reactiveValueWrite setRV nCell
183 hideNa = do widgetHide slideCombo
186 widgetHideAll noteDurBox
188 showNa = do widgetShow slideCombo
191 widgetShowAll noteDurBox
192 updateNaBox :: GUICell -> IO ()
193 updateNaBox GUICell { cellAction = act } = case act of
198 reactiveValueOnCanRead setRV $ postGUIAsync $ do
199 nCell <- reactiveValueRead setRV
200 fromMaybeM_ (reactiveValueWriteOnNotEq artComboRV . naArt <$>
201 getNAttr (cellAction nCell))
202 fromMaybeM_ (reactiveValueWriteOnNotEq slideComboRV . ornSlide . naOrn <$>
203 getNAttr (cellAction nCell))
204 reactiveValueWriteOnNotEq rCountRV $ repeatCount nCell
205 fromMaybeM_ (reactiveValueWriteOnNotEq noteDurRV . naDur <$>
206 getNAttr (cellAction nCell))
210 state <- newEmptyMVar
212 (\iPos -> liftIO $ do
213 postGUIAsync $ void $ tryPutMVar state iPos
218 button <- eventButton
221 mp <- boardGetPiece fPos board
222 mstate <- tryTakeMVar state
223 when (fPos `elem` validArea && isJust mp) $ do
224 let piece = snd $ fromJust mp
225 when (button == RightButton && maybe False (== fPos) mstate) $
226 boardSetPiece fPos (BF.second rotateGUICell (Player,piece)) board
227 nmp <- boardGetPiece fPos board
228 when (button == LeftButton && isJust nmp) $ do
229 let nC = snd $ fromJust nmp
230 reactiveValueWrite setRV (fPos,nC)
231 fromMaybeM_ $ reactiveValueWrite artComboRV . naArt <$>
232 getNAttr (cellAction nC)
234 reactiveValueWrite slideComboRV . ornSlide . naOrn <$> getNAttr (cellAction nC)
235 reactiveValueWrite rCountRV $ repeatCount nC
236 fromMaybeM_ $ reactiveValueWrite noteDurRV . naDur <$>
237 getNAttr (cellAction nC)
241 reactiveValueOnCanRead setRV (reactiveValueRead setRV >>= updateNaBox . snd)
247 --setMCBMVar <- newMCBMVar =<< reactiveValueRead setRV
248 --setMCBMVar =:= setRV
251 return (pieceBox,setRV)