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