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