]> Git — Sourcephile - tmp/julm/arpeggigon.git/blob - src/RMCA/Semantics.hs
Extend types of Split Action
[tmp/julm/arpeggigon.git] / src / RMCA / Semantics.hs
1 -- Basic Semantics V2 for a Reactive Music Cellular Automaton.
2 -- Inspired by the reacTogon.
3 -- Written by Henrik Nilsson, 2016-05-27
4 -- Based on an earlier version.
5 --
6 -- This gives the semantics of a single RMCA layer. The output is
7 -- a high-level representation of notes for each beat. This is to be
8 -- translated to low-level MIDI message by a subsequent translator
9 -- responsible for merging notes from different layers, ensuring that
10 -- a note off message corresponding to each note on message is always
11 -- emitted after the appropriate time, rendering any embellismnets
12 -- such as slides (while not generating too much MIDI data), etc.
13
14 -- ToDo:
15 -- * Add boolean flag to change direction to indicate start tile
16 -- DONE!
17 -- * Change main routine to generate start play heads from board
18 -- DONE!
19 -- * Add an optional restart facility: Maybe Int, restart every n
20 -- bars.
21 -- DONE!
22 -- * Interpret a negative repeat as repeat indefinitely.
23 -- DONE!
24 -- * Interpret a non-positve duration as mute: don't emit any note.
25 -- DONE!
26 -- * Eliminate Ignore as now almost the same as Absorb with duration 0?
27 -- The only difference is that Absorb mostly overrides the repeat count.
28 -- Absorb = Stop {duration 0, repeat 1}
29 -- And as absorb might be a common case, it might be useful to have
30 -- a distinct graphical representation?
31 -- DECIDED AGAINST FOR NOW
32
33 module RMCA.Semantics where
34
35 import Debug.Trace
36 import Data.Array
37 import Data.List (intercalate, nub)
38 import Data.Maybe (catMaybes, fromJust)
39 import RMCA.Auxiliary
40
41
42 ------------------------------------------------------------------------------
43 -- Basic Type Synonyms
44 ------------------------------------------------------------------------------
45
46 type InstrumentNo = Int
47
48 -- Unipolar control value; [0, 1]
49 type UCtrl = Double
50
51 -- Bipolar control value; [-1, 1]
52 type BCtrl = Double
53
54 -- Unipolar control values are usually between 0 and 127.
55 toUCtrl :: Int -> UCtrl
56 toUCtrl x = fromIntegral x / 127
57
58 fromUCtrl :: UCtrl -> Int
59 fromUCtrl x = floor $ bound (0,1) x * 127
60
61 -- Bipolar control values are usually between -127 and 127.
62 toBCtrl :: Int -> BCtrl
63 toBCtrl = toUCtrl
64
65 fromBCtrl :: BCtrl -> Int
66 fromBCtrl = fromUCtrl
67
68 ------------------------------------------------------------------------------
69 -- Tempo
70 ------------------------------------------------------------------------------
71
72 type Tempo = Int
73
74 ------------------------------------------------------------------------------
75 -- Time and Beats
76 ------------------------------------------------------------------------------
77
78 -- The assumption is that the automaton is clocked by a beat clock and
79 -- thus advances one step per beat. For an automaton working in real time,
80 -- the beat clock would be defined externally, synchronized with other
81 -- layers and possibly external MIDI, and account for tempo, any swing, etc.
82
83 -- Beats and Bars
84
85 -- Beats per Bar: number of beats per bar in the time signature of a layer.
86 -- Non-negative.
87 type BeatsPerBar = Int
88
89 -- The beat number in the time signature of the layer. The first beat is 1.
90 type BeatNo = Int
91
92 nextBeatNo :: BeatsPerBar -> BeatNo -> BeatNo
93 nextBeatNo bpb bn = bn `mod` bpb + 1
94
95
96 {-
97 -- Not needed for individual layers (at present)
98
99 -- Time; [0,+inf)
100 type Time = Double
101 -}
102
103
104 ------------------------------------------------------------------------------
105 -- MIDI
106 ------------------------------------------------------------------------------
107
108 -- This semantics mainly works with a high-level represemntation of notes.
109 -- But it is convenient to express some of the high-level aspects directly
110 -- in the corresponding MIDI terms to facilitate the translation.
111
112 -- MIDI note number; [0,127]
113 type MIDINN = Int
114
115
116 -- Assume MIDI convetion: 60 = "Middle C" = C4
117 middleC :: Int
118 middleC = 60
119 middleCOct :: MIDINN
120 middleCOct = 4
121
122
123 -- MIDI velocity; [0,127]
124 type MIDIVel = Int
125
126
127 -- MIDI Program Change: Program Number; [0,127]
128 type MIDIPN = Int
129
130
131 -- MIDI Control Change: Control Number and Control Value; [0,127]
132 type MIDICN = Int
133 type MIDICV = Int
134
135 -- MIDICVRnd gives the option to pick a control value at random.
136 -- (Handled through subsequent translation to low-level MIDI events.)
137 data MIDICVRnd = MIDICV MIDICV | MIDICVRnd deriving (Eq, Show, Read)
138
139 --
140 ------------------------------------------------------------------------------
141 -- Notes
142 ------------------------------------------------------------------------------
143
144 -- Pitch
145
146 -- We chose to represent pitch by MIDI note number
147 newtype Pitch = Pitch MIDINN deriving Eq
148
149 pitchToMNN :: Pitch -> MIDINN
150 pitchToMNN (Pitch nn) = nn
151
152 instance Show Pitch where
153 show (Pitch nn) = names !! note ++ show oct
154 where
155 nn' = nn - middleC
156 note = nn' `mod` 12
157 oct = nn' `div` 12 + middleCOct
158 names = ["C", "C#", "D", "D#", "E", "F",
159 "F#", "G", "G#", "A", "A#", "B"]
160
161 -- Relative pitch in semi tones. Used for e.g. transposition.
162 type RelPitch = Int
163
164
165 -- Articulation
166
167 -- Each layer has a setting that indicate how strongly the notes
168 -- should normally be played as a percentage of full strength.
169 -- (In the real application, this settig can be set to a fixed value
170 -- or set to be derived from teh last input note, "as played").
171 -- Individual notes can tehn be accented (played more strongly),
172 -- either unconditionally or as a function of the beat count.
173
174 type Strength = UCtrl
175
176 -- This could of course be generalised, e.g. a list of beat numbers to
177 -- accentuate. But this is simple and accounts for the most common patterns.
178 data Articulation = NoAccent
179 | Accent
180 | Accent1
181 | Accent13
182 | Accent14
183 | Accent24
184 deriving (Eq, Show, Read, Enum)
185
186 accentStrength :: Strength
187 accentStrength = 1.2
188
189 -- Articulated strength
190 articStrength :: Strength -> BeatNo -> Articulation -> Strength
191 articStrength st bn art
192 | accentedBeat = st * accentStrength
193 | otherwise = st
194 where
195 accentedBeat =
196 case (bn, art) of
197 (_, NoAccent) -> False
198 (_, Accent) -> True
199 (1, Accent1) -> True
200 (1, Accent13) -> True
201 (3, Accent13) -> True
202 (1, Accent14) -> True
203 (4, Accent14) -> True
204 (1, Accent24) -> True
205 (4, Accent24) -> True
206 _ -> False
207
208
209 -- Duration
210
211 -- Duration in terms of a whole note at the *system* tempo. (Each layer
212 -- is clocked at a layer beat that is a fraction/multiple of the system
213 -- tempo). Note that notes are played a little shorter than their nominal
214 -- duration. This is taken care of by the translation into low-level
215 -- MIDI events. (One might consider adding indications of staccato or
216 -- tenuto.)
217 --
218 -- A non-positive duration is interpreted as mute: no note emitted.
219 type Duration = Rational
220
221
222 -- Ornamentation
223
224 -- Notes can be ornamented. Traditionnally, ornamenting refers to modifications
225 -- of the pitch, such as a trill or a grace note. Here we use the term in
226 -- a generalised sense.
227 -- * A MIDI program change (to be sent before the note).
228 -- * A MIDI Continuous Controler Change (to be sent before the note).
229 -- * A Slide
230 -- One might also consider adding trills, grace notes, MIDI after touch ...
231
232 data Ornaments = Ornaments {
233 ornPC :: Maybe MIDIPN,
234 ornCC :: [(MIDICN, MIDICVRnd)],
235 ornSlide :: SlideType
236 } deriving (Show,Read,Eq)
237
238 data SlideType = NoSlide | SlideUp | SlideDn deriving (Eq, Show, Enum, Read)
239
240 noOrn :: Ornaments
241 noOrn = Ornaments { ornPC = Nothing
242 , ornCC = []
243 , ornSlide = NoSlide
244 }
245
246 -- Notes
247
248 -- Attributes needed to generate a note.
249 -- * The pitch of a note is given by the position on the board
250 -- * The strength is given by the layer strength, beat no., and articulation
251 -- * Duratio and Ornamentatio are stored
252 data NoteAttr = NoteAttr {
253 naArt :: Articulation,
254 naDur :: Duration,
255 naOrn :: Ornaments
256 } deriving (Show,Read,Eq)
257
258 noNoteAttr :: NoteAttr
259 noNoteAttr = NoteAttr { naArt = NoAccent
260 , naDur = 0
261 , naOrn = noOrn
262 }
263
264 -- High level note representation emitted form a layer
265 data Note = Note {
266 notePch :: Pitch,
267 noteStr :: Strength,
268 noteDur :: Duration,
269 noteOrn :: Ornaments
270 } deriving (Show,Eq)
271
272
273 ------------------------------------------------------------------------------
274 -- Board
275 ------------------------------------------------------------------------------
276
277 -- Numbering; row number inside tile, column number below:
278 -- _ _
279 -- _/2\_/2\_
280 -- / \_/1\_/1\
281 -- \_/1\_/1\_/
282 -- / \_/0\_/0\
283 -- \_/0\_/0\_/
284 -- \_/ \_/
285 -- -1 0 1 2
286
287
288 -- Angle measured in multiples of 60 degrees.
289 type Angle = Int
290
291 data Dir = N | NE | SE | S | SW | NW deriving (Enum, Bounded, Eq, Show, Read)
292
293 predDir :: Dir -> Dir
294 predDir d | d == minBound = maxBound
295 | otherwise = pred d
296
297 nextDir :: Dir -> Dir
298 nextDir d | d == maxBound = minBound
299 | otherwise = succ d
300
301 turn :: Dir -> Angle -> Dir
302 turn d a = toEnum ((fromEnum d + a) `mod` 6)
303
304 type Pos = (Int, Int)
305
306 -- Position of neighbour in given direction
307 neighbor :: Dir -> Pos -> Pos
308 neighbor N (x,y) = (x, y + 1)
309 neighbor NE (x,y) = (x + 1, y + 1 - x `mod` 2)
310 neighbor SE (x,y) = (x + 1, y - x `mod` 2)
311 neighbor S (x,y) = (x, y - 1)
312 neighbor SW (x,y) = (x - 1, y - x `mod` 2)
313 neighbor NW (x,y) = (x - 1, y + 1 - x `mod` 2)
314
315
316 -- Position and transposition to pitch:
317 -- * Harmonic Table" layout: N = +7; NE = +4; SE = -3
318 -- * (0,0) assumed to be "Middle C"
319 posToPitch :: Pos -> RelPitch -> Pitch
320 posToPitch (x,y) tr =
321 Pitch (y * 7 + x `div` 2 - 3 * (x `mod` 2) + middleC + tr)
322
323
324 -- Actions
325 -- A ChDir counter is optionally a start counter if the Boolean flag is
326 -- set to true.
327 -- Any counter can be made silent by setting the note duration to a
328 -- non-positive number.
329
330 data Action = Inert -- No action, play heads move through.
331 | Absorb -- Remove play head silently.
332 | Stop NoteAttr -- Play note then remove play head.
333 | ChDir Bool NoteAttr Dir -- Play note then change direction.
334 | Split NoteAttr [Int] -- Play note then split head into more than one.
335 -- | Split NoteAttr -- Play note then split head into five.
336 deriving (Show,Read,Eq)
337
338 dirList :: [(String, [Int])]
339 dirList = [ ("0 1 2 3 4 5", [0, 1, 2, 3, 4, 5])
340 , ("0 1 2 3 4", [0, 1, 2, 3, 4])
341 , ("0 1 2 3", [0, 1, 2, 3])
342 , ("0 1 2 4", [0, 1, 2, 4])
343 , ("0 1 3 4", [0, 1, 3, 4])
344 , ("0 1 2", [0, 1, 2])
345 , ("0 1 3", [0, 1, 3])
346 , ("0 2 3", [0, 2, 3])
347 , ("0 2 4", [0, 2, 4])
348 , ("0 1", [0, 1])
349 , ("0 2", [0, 2])
350 , ("0 3", [0, 3])
351 ]
352
353 turnQueue :: [Int] -> Int -> [Int]
354 turnQueue ds n = sortQueue [] $ map ((`mod` 6) . (+ n)) ds
355
356 sortQueue :: [Int] -> [Int] -> [Int]
357 sortQueue [] ys = sortQueue [head ys] (tail ys)
358 sortQueue xs [] = xs
359 sortQueue xs ys = case last xs > head ys of
360 True -> ys ++ xs
361 False -> sortQueue (xs ++ [head ys]) (tail ys)
362
363 fromProto :: [Int] -> ([Int], Int)
364 fromProto ds = fromJust $ lookup s rotates where
365 s = minimum $ map fst rotates
366 rotates = [(sum ds', (ds', d)) | d <- ds, let ds' = turnQueue ds (-d)]
367
368 -- Contains a list of all the actions. Useful to have for e.g. pixbufs
369 -- generation. It is shared for all applications from here to avoid
370 -- forgetting to add a case if future actions are added.
371 actionList :: [Action]
372 actionList = [ Inert
373 , Absorb
374 , Stop noNoteAttr
375 ] ++
376 [ Split noNoteAttr ds | proto <- map snd dirList
377 , offset <- [0..6]
378 , let ds = turnQueue proto offset
379 ] ++
380 [ ChDir t noNoteAttr d | t <- [True, False]
381 , d <- [minBound..maxBound]
382 ]
383
384 anonymizeConstructor :: Action -> Action
385 anonymizeConstructor Inert = Inert
386 anonymizeConstructor Absorb = Absorb
387 anonymizeConstructor (Stop _) = Stop noNoteAttr
388 anonymizeConstructor (Split _ ds) = Split noNoteAttr ds
389 anonymizeConstructor (ChDir t _ d) = ChDir t noNoteAttr d
390
391 -- Cells
392 -- A cell stores an action and a repetition number.
393 -- 0: the cell is completely bypassed, as if it wasn't there.
394 -- 1: the action is carried out once (default)
395 -- n > 1: any note output of the action is repeated (n-1) times before the
396 -- action is carried out.
397 -- n < 0: any note output of the action is repeated indefinitely (oo).
398
399 type Cell = (Action, Int)
400
401
402 -- Make a cell with a default repeat count of 1.
403 mkCell :: Action -> Cell
404 mkCell a = mkCellRpt a 1
405
406
407 -- Make a cell with a non-default repeition number.
408 mkCellRpt :: Action -> Int -> Cell
409 mkCellRpt a n = (a, n)
410
411
412 -- Board extent: south-west corner and north-east corner.
413 -- This covers most of the MIDI range: A#-1 (10) to G7 (103).
414 swc, nec :: Pos
415 swc = (-9, -6)
416 nec = (9, 6)
417
418
419 -- Test if a position is on the board as defined by swc and nec.
420 -- The assumption is that odd columns contain one more cell, as per the
421 -- picture above. Of course, one could opt for a "zig-zag" layout
422 -- with each column having the same number of cells which would be slightly
423 -- simpler.
424 onBoard :: Pos -> Bool
425 onBoard (x,y) = xMin <= x && x <= xMax
426 && yMin <= y
427 && (if even x then
428 y < yMax
429 else
430 y <= yMax)
431 where
432 (xMin, yMin) = swc
433 (xMax, yMax) = case nec of
434 (x, y) | even x -> (x, y + 1)
435 | otherwise -> (x, y)
436
437
438 type Board = Array Pos Cell
439
440
441 -- Build a board from a list specifying the non-empty cells.
442 makeBoard :: [(Pos, Cell)] -> Board
443 makeBoard pcs =
444 array (swc,nec')
445 ([(p, if onBoard p then mkCell Inert else mkCell Absorb)
446 | p <- range (swc, nec')]
447 ++ [(p,c) | (p, c) <- pcs, onBoard p])
448 where
449 -- This is to ensure (neighbor NW nec) is included on the board,
450 -- regardless of whether the column of nec is even or odd.
451 -- Otherwise, due to the "jagged" upper edge, the top row would
452 -- be missing, but every other cell of that *is* on the board.
453 -- The "superfluous" cells are set to Absorb above.
454 nec' = neighbor N nec
455
456
457 -- Look up a cell
458 lookupCell :: Board -> Pos -> Cell
459 lookupCell b p = if onBoard p then b ! p else (Absorb, 1)
460
461
462 ------------------------------------------------------------------------------
463 -- Play Head
464 ------------------------------------------------------------------------------
465
466 -- A play head is characterised by:
467 -- * Current position
468 -- * Number of beats before moving
469 -- * Direction of travel
470 -- If an action involves playing a note, this is repeated once for
471 -- each beat the play head is staying, with the rest of the action
472 -- carried out at the last beat.
473
474 data PlayHead =
475 PlayHead {
476 phPos :: Pos,
477 phBTM :: Int,
478 phDir :: Dir
479 }
480 deriving (Eq, Show)
481
482
483 ------------------------------------------------------------------------------
484 -- Start Heads
485 ------------------------------------------------------------------------------
486
487 startHeads :: Board -> [PlayHead]
488 startHeads bd =
489 [ PlayHead {
490 phPos = p,
491 phBTM = n,
492 phDir = d
493 }
494 | (p, (ChDir True _ d, n)) <- assocs bd ]
495
496
497 ------------------------------------------------------------------------------
498 -- State transition
499 ------------------------------------------------------------------------------
500
501 -- Advance the state of a single play head.
502 --
503 -- The result is a list of heads to be actioned at the *next* beat
504 -- later) and possibly a note to be played at *this* beat.
505
506 advanceHead :: Board -> BeatNo -> RelPitch -> Strength -> PlayHead
507 -> ([PlayHead], Maybe Note)
508 advanceHead bd bn tr st ph = ahAux (moveHead bd ph)
509 where
510 ahAux ph@PlayHead {phPos = p, phBTM = btm, phDir = d} =
511 case fst (lookupCell bd p) of
512 Inert -> ([ph], Nothing)
513 Absorb -> ([], Nothing) -- No point waiting until BTM=0
514 Stop na -> (newPHs [], mkNote p bn tr st na)
515 ChDir _ na d' -> (newPHs [ph {phDir = d'}],
516 mkNote p bn tr st na)
517 Split na ds -> (newPHs [ PlayHead {
518 phPos = p,
519 phBTM = 0,
520 phDir = d'
521 }
522 | a <- ds,
523 let d' = turn N a
524 ],
525 mkNote p bn tr st na)
526 where
527 newPHs phs = if btm == 0 then phs else [ph]
528
529
530 -- Moves a play head if the BTM counter has reached 0, otherwise decrement BTM.
531 -- Any encountered cells where the repeat count is < 1 are skipped.
532 moveHead :: Board -> PlayHead -> PlayHead
533 moveHead bd (ph@PlayHead {phPos = p, phBTM = btm, phDir = d})
534 | btm == 0 = let
535 p' = neighbor d p
536 btm' = snd (lookupCell bd p')
537 in
538 moveHead bd (ph {phPos = p', phBTM = btm'})
539 | btm > 0 = ph {phBTM = btm - 1}
540 | otherwise = ph -- Repeat indefinitely
541
542 mkNote :: Pos -> BeatNo -> RelPitch -> Strength -> NoteAttr -> Maybe Note
543 mkNote p bn tr st na@NoteAttr {naDur = d}
544 | d <= 0 = Nothing -- Notes of non-positive length are silent.
545 | otherwise = Just
546 Note {
547 notePch = posToPitch p tr,
548 noteStr = articStrength st bn (naArt na),
549 noteDur = naDur na,
550 noteOrn = naOrn na
551 }
552
553
554 -- Advance a list of heads, collecting all resulting heads and notes.
555 -- Any duplicate play heads are eliminated (or their number may uselessly
556 -- grow very quickly), and a cap (50, arbitrary, but should be plenty,
557 -- expecially given the board size) on the number of simultaneous playheads
558 -- per layer is imposed.
559 advanceHeads :: Board -> BeatNo -> RelPitch -> Strength -> [PlayHead]
560 -> ([PlayHead], [Note])
561 advanceHeads bd bn tr st phs =
562 let
563 (phss, mns) = unzip (map (advanceHead bd bn tr st) phs)
564 in
565 (take 50 (nub (concat phss)), catMaybes mns)
566
567
568 -- Given a board with start counters, run a board indefinitely, optionally
569 -- restarting every ri bars.
570 --
571 -- Arguments:
572 -- (1) Board (bd)
573 -- (2) Beats Per Bar (bpb); > 0
574 -- (3) Optioal repeat Interval (mri); In bars.
575 -- (4) Transposition (tr)
576 -- (5) Strength (st)
577 --
578 -- Returns:
579 -- Stream of notes played at each beat.
580 --
581 -- In the real implementation:
582 -- * A layer beat clock would be derived from the system beat (as a
583 -- fraction/multiple, adding any swing) and each clock event be tagged
584 -- with the beat number.
585 -- * The board (bd) would not necessarily be a constant input. (One might
586 -- consider allowing editing a layer while the machine is running)
587 -- * The time signature, and thus the beats per par (bpb), along with
588 -- repeat interval (ri) would likely be static (only changeable while
589 -- automaton is stopped).
590 -- * The transposition (tr) would be dynamic, the sum of a per layer
591 -- transposition that can be set through the user interface and the
592 -- difference between the MIDI note number of the last external
593 -- note received for the layer and middle C (say).
594 -- * The strength (st) would be dynamic, configurable as either the strength
595 -- set through the user interface or the strength of the last external
596 -- note received for the layer (derived from its MIDI velocity).
597
598 runRMCA :: Board -> BeatsPerBar -> Maybe Int -> RelPitch -> Strength
599 -> [[Note]]
600 runRMCA bd bpb mri tr st
601 | bpb > 0 =
602 case mri of
603 Nothing -> nss
604 Just ri
605 | ri > 0 -> cycle (take (ri * bpb) nss)
606 | otherwise -> error "The repeat interval must be at \
607 \least 1 bar."
608 | otherwise = error "The number of beats per bar must be at least 1."
609 where
610 nss = runAux 1 (startHeads bd)
611
612 runAux bn phs = ns : runAux (nextBeatNo bpb bn) phs'
613 where
614 (phs', ns) = advanceHeads bd bn tr st phs
615
616
617 -- Print played notes in a time-stamped (bar, beat), easy-to-read format.
618
619 ppNotes :: BeatsPerBar -> [[Note]] -> IO ()
620 ppNotes bpb nss = ppnAux (zip [(br,bn) | br <- [1..], bn <- [1..bpb]] nss)
621 where ppnAux :: [((Int,BeatsPerBar),[Note])] -> IO ()
622 ppnAux [] = return ()
623 ppnAux ((_, []) : tnss) = ppnAux tnss
624 ppnAux ((t, ns) : tnss) = do
625 putStrLn (leftJustify 10 (show t) ++ ": "
626 ++ intercalate ", " (map show ns))
627 ppnAux tnss
628
629
630 leftJustify :: Int -> String -> String
631 leftJustify w s = replicate (w - length s) ' ' ++ s
632
633 {-
634 ------------------------------------------------------------------------------
635 -- Simple tests
636 ------------------------------------------------------------------------------
637
638 testBoard1 =
639 makeBoard [((0,0), mkCell (ChDir True na1 N)),
640 ((0,1), mkCell (ChDir False na1 SE)),
641 ((1,1), mkCell (Split na1)),
642 ((1,-1), mkCell (Split na1)),
643 ((-1,0), mkCell (ChDir False na2 NE))]
644
645 testBoard1a =
646 makeBoard [((0,0), mkCell (ChDir False na1 N)),
647 ((0,1), mkCell (ChDir False na1 SE)),
648 ((1,1), mkCell (Split na1)),
649 ((1,-1), mkCell (Split na1)),
650 ((-1,0), mkCell (ChDir False na2 NE))]
651
652 testBoard2 =
653 makeBoard [((0,0), mkCell (ChDir True na1 N)),
654 ((0,2), mkCellRpt (ChDir False na2 SE) 3),
655 ((2,1), mkCell (ChDir False na1 SW)),
656 ((1,1), mkCellRpt (ChDir False na1 N) 0) {- Skipped! -},
657 ((0,4), mkCellRpt (ChDir True na1 N) (-1)) {- Rpt indef. -},
658 ((0, -6), mkCell (ChDir True na1 N)),
659 ((0, -2), mkCell (ChDir False na3 S) {- Silent -})]
660
661 testBoard3 =
662 makeBoard [((0,0), mkCell (ChDir True na1 N))]
663
664 na1 = NoteAttr {
665 naArt = Accent13,
666 naDur = 1 % 4,
667 naOrn = Ornaments Nothing [] NoSlide
668 }
669
670 na2 = NoteAttr {
671 naArt = NoAccent,
672 naDur = 1 % 16,
673 naOrn = Ornaments Nothing [(10, MIDICVRnd)] SlideUp
674 }
675
676 na3 = NoteAttr {
677 naArt = Accent13,
678 naDur = 0,
679 naOrn = Ornaments Nothing [] NoSlide
680 }
681
682
683 bpb :: Int
684 bpb = 4
685
686 main = ppNotes bpb (take 50 (runRMCA testBoard3 bpb (Just 2) 0 0.8))
687 -}