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