]> git.donarmstrong.com Git - lilypond.git/blob - ly/articulate.ly
Merge remote-tracking branch 'origin/translation'
[lilypond.git] / ly / articulate.ly
1 %
2 % Copyright (C) 2008, 2009, 2010, 2011 NICTA
3 % Author: Peter Chubb <peter.chubb AT nicta.com.au>
4 % $Id: articulate.ly,v 1.7 2011-03-24 00:40:00 peterc Exp $
5 %
6 %
7 %  This program is free software; you can redistribute it and/or modify
8 %  it under the terms of the GNU General Public License, version 3,
9 %  as published by the Free Software Foundation.
10 %
11 %  WARNING: this file under GPLv3 only, not GPLv3+
12 %
13 %  This program is distributed in the hope that it will be useful,
14 %  but WITHOUT ANY WARRANTY; without even the implied warranty of
15 %  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
16 %  See the GNU General Public License for more details.  It is
17 %  available in the Lilypond source tree, or at
18 %  http://www.gnu.org/licenses/gpl-3.0.html
19 %
20 % This script tries to make MIDI output from LilyPond a little more realistic.
21 % It tries to take articulations (slurs, staccato, etc) into account, by
22 % replacing notes  with sequential music of suitably time-scaled note plus
23 % skip.
24 %
25 % It also tries to unfold trills turns etc., and take rallentendo
26 % and accelerando into account.
27 %
28 % As my scheme knowledge is poor (I was teaching myself as I went), there
29 % is much scope for improvement.
30
31 %
32 %%%USAGE
33 % In the \score section do:
34 % \articulate <<
35 %       all the rest of the score
36 % >>
37 % or use the lilywrap script.
38 %
39 % TO DO (prioritised, the ones that'll make the most difference first)
40 %
41 % * Dynamics.
42 %   * Fix quantisation for dynamics on single note (replace note
43 %     with tied 128th notes?) -- started, needs work.
44 %   * Make \fp do the right thing (loud start, then quiet).
45 %
46 % * Inegalite.  Notes on-beat steal time from notes off-beat.
47 %   Degree of stealing is a parameter: from 1.0 (straight)
48 %   to 1.5 (extreme swing).  Also fix tenuto to use this.
49 %
50 % * add accel (to match rall), and molto rall. I've never seen
51 %   molto accel but some composer somewhere has probably used it.
52 %
53 % * Fermata, and Fermata Lunga
54 % * Add more synonyms for accel and rall: rit ritard stringendo
55 %
56 % * Phrasing.
57 %   * Rall at end of piece
58 %   * Very slight accel into a phrase, rall out of it.
59 %   * Dynamics during a phrase????  unclear how these should be in
60 %     the general case
61 %
62 % * Trill algorithm needs work.
63 %
64 % * Cope with more ornaments/articulations.
65 %    inverted-turns, etc.
66 %   -- accent needs better control of dynamics.
67 %   -- Articulations: mezzo-staccato, portato.
68 %   -- Handling of generic ornaments (in lily, `\stopped'; in
69 %               most early music:  ornament this note (trill, turn
70 %               or mordent as the player wishes))
71 % * Automatic gruppetto at end of trill; better handling of
72 %      initial/final grace notes on trill
73 % * Automatic ornaments.
74 %   * Spot cadences and ornament
75 %   * Look for quaver-dotted note for trills, for example.
76 %   * Fill in steps. (Needs lookahead/lookbehind.)
77 % * `afterturn' -- a turn after the start of a note.
78 % * accidentals for trills and turns
79
80 % CHANGELOG
81 %  * David Kastrup: basic 2.15.28 compatibility by using event-chord-wrap!
82 %    This should really be done by rewriting the code more thoroughly.
83 %  * From Iain Nicol: appoggiatura timings were out; add staccatissimo; fix
84 %    trillSpanner endpoints.
85 %  * Also handle Breathing events (by throwing them away).  This isn't ideal;
86 %    one should really shorten the note before a little.  But I don't know
87 %    how to do lookahead in scheme.
88 %  * Also ignore explicit line breaks.
89 %  * Add Mordents (reported by Patrick Karl)
90 %
91
92 \version "2.16.0"
93
94 #(use-modules (srfi srfi-1))
95 #(use-modules (ice-9 debug))
96 #(use-modules (scm display-lily))
97
98 % PARAMETERS
99 % How much to compress notes marked Staccato.  CPE Bach says `as short as
100 % may conveniently be played, as if the keys were too hot to touch'.
101 % Most modern sources say 1/2 the notated length of a note.
102 #(define ac:staccatoFactor '(1 . 2))
103
104 % How much to compress notes marked staccatissimo.
105 #(define ac:staccatissimoFactor '(1 . 4))
106
107 % And tenuto (if we ever implement time stealing, this should be >1.0)
108 #(define ac:tenutoFactor '(1 . 1))
109
110 % How much to articulate normal notes.  CPE Bach says 1/2 (and
111 % staccato should be `as short as may conveniently be played') but this
112 % sounds too short for modern music.  7/8 sounds about right.
113 #(define ac:normalFactor '(7 . 8))
114
115 % How much to slow down for a rall. or a poco rall.
116 % (or speed up for accel or poco accel)
117 #(define ac:rallFactor (ly:make-moment 60 100)) % 40% slowdown
118 #(define ac:pocoRallFactor (ly:make-moment 90 100)) % 10% slowdown
119
120 % The absolute time for a twiddle in a trill, in minutes.
121 % Start with 1/4 seconds == 1/240 minutes
122 #(define ac:maxTwiddleTime (ly:make-moment 1 240))
123
124 % How long ordinary grace notes should be relative to their notated
125 % duration.  9/40 is LilyPond's built-in behaviour for MIDI output
126 % (though the notation reference says 1/4).
127 #(define ac:defaultGraceFactor 9/40)
128
129 % What proportion of an ordinary grace note's time should be stolen
130 % from preceding notes (as opposed to stealing from the principal note).
131 % Composers' intentions for this vary.  Taking all from the preceding
132 % notes is LilyPond's built-in behaviour for MIDI output.
133 #(define ac:defaultGraceBackwardness 1)
134
135
136 % Internal variables, don't touch.
137 % (should probably be part of a context somehow)
138
139 % Whether to slur, or not
140 #(define ac:inSlur #f)
141 #(define ac:inPhrasingSlur #f)
142
143 % Whether the current noteevent is in a trill spanner
144 #(define ac:inTrill #f)
145
146 % assume start in C major.  Key change events override this.
147 % Could get from context, but don't know how.
148 #(define ac:current-key (make-music
149           'KeyChangeEvent
150           'tonic
151           (ly:make-pitch -1 0 0)
152           'pitch-alist
153           (list (cons 0 0)
154                 (cons 1 0)
155                 (cons 2 0)
156                 (cons 3 0)
157                 (cons 4 0)
158                 (cons 5 0)
159                 (cons 6 0))))
160
161
162 #(define ac:currentTempo (ly:make-moment 15 1)) % 4 = 60, measured wholes per minute
163 #(define ac:lastTempo ac:currentTempo) % for 'a tempo' or 'tempo I'
164
165 % The duration of the current note.  Start at a crotchet
166 % for no good reason.
167 #(define ac:currentDuration (ly:make-duration 2 0 1 1))
168
169 % Amount of musical time (in whole notes) that we need to steal from the
170 % next events seen.
171 #(define ac:stealForward 0)
172
173 % List of events in the output so far, in reverse order, from which we can
174 % steal time.
175 #(define ac:eventsBackward '())
176
177 % Log events for the backward chain.
178 #(define (ac:logEventsBackward music)
179   (music-map
180    (lambda (m)
181     (case (ly:music-property m 'name)
182      ((EventChord)
183       (set! ac:eventsBackward (cons m ac:eventsBackward))
184       m)
185      ((BarCheck SkipMusic)
186       (let ((wm (make-sequential-music (list m))))
187        (set! ac:eventsBackward (cons wm ac:eventsBackward))
188        wm))
189      (else
190       m)))
191    music))
192
193 % Steal time from the backward chain.  Adds to ac:stealForward (with a
194 % warning) if it couldn't backward-steal all that was desired.
195 #(define (ac:stealTimeBackward tosteal)
196   (if (<= tosteal 0)
197    #t
198    (if (null? ac:eventsBackward)
199     (begin
200      (ly:warning (_ "articulation failed to steal ~a note backward at beginning of music; stealing forward instead") tosteal)
201      (set! ac:stealForward (+ ac:stealForward tosteal)))
202     (let*
203      ((lastev (car ac:eventsBackward))
204       (levlen (ly:moment-main (ly:music-length lastev))))
205      (if (< tosteal levlen)
206       (begin
207        (ly:music-compress lastev (ly:make-moment (/ (- levlen tosteal) levlen)))
208        #t)
209       (begin
210        (if (any (lambda (z) (eq? 'NoteEvent (ly:music-property z 'name)))
211                 (ly:music-property lastev 'elements))
212         (ly:warning (_ "stealing the entirety of a note's time")))
213        (set! (ly:music-property lastev 'elements) '())
214        (set! ac:eventsBackward (cdr ac:eventsBackward))
215        (ac:stealTimeBackward (- tosteal levlen))))))))
216
217 % Debugging: display a moment plus some text.
218 % Returns its moment argument so can be used in-line.
219 #(define (display-moment  text m)
220   (display text)
221   (display (list (ly:moment-main-numerator m) "/" (ly:moment-main-denominator m)))
222   m
223 )
224
225 % Track tempo (and maybe later, other context properties)
226 % as they change.  Needs to better cope with saving only Tempo I,
227 % otherwise "a tempo" goes back to the tempo before the last change.
228 #(define (ac:adjust-props sym music)
229   (case sym
230    ((tempoWholesPerMinute)
231     (set! ac:currentTempo (ly:music-property music 'value))
232     (set! ac:lastTempo ac:currentTempo)
233   )))
234
235 % Raise note one step in the current diatonic scale.
236 #(define (ac:up note)
237   (let* ((pitch (ly:music-property note 'pitch))
238          (notename (ly:pitch-notename pitch))
239          (new-notename (if (eq? notename 6) 0 (+ 1 notename)))
240          (alterations (ly:music-property ac:current-key 'pitch-alist))
241          (new-alteration (cdr (assq new-notename alterations)))
242          (new-octave (if (eq? new-notename 0) (+ 1 (ly:pitch-octave pitch))
243                       (ly:pitch-octave pitch)))
244        )
245    (set! (ly:music-property note 'pitch)(ly:make-pitch new-octave new-notename new-alteration))))
246
247
248 % Lower note one step in the current diatonic scale.
249 #(define (ac:down note)
250   (begin  (let* ((pitch (ly:music-property note 'pitch))
251          (notename (ly:pitch-notename pitch))
252          (new-notename (if (eq? notename 0) 6 (- notename 1)))
253          (alterations (ly:music-property ac:current-key 'pitch-alist))
254          (new-alteration (cdr (assq new-notename alterations)))
255          (new-octave (if (eq? new-notename 6) (- (ly:pitch-octave pitch) 1)
256                       (ly:pitch-octave pitch)))
257        )
258    (set! (ly:music-property note 'pitch)(ly:make-pitch new-octave new-notename new-alteration))))
259 )
260
261 % Shorten a note, and save the note's original duration in ac:currentDuration
262 #(define (ac:articulate-one-note m fraction)
263   "Replace m with m*fraction"
264   (if  (eq? 'NoteEvent (ly:music-property m 'name))
265    (let*
266     ((dur (ly:music-property m 'duration))
267      (l (ly:duration-log dur))
268      (d (ly:duration-dot-count dur))
269      (factor (ly:duration-factor dur))
270      (num (car fraction))
271      (denom (cdr fraction)))
272     (begin
273      (set! ac:currentDuration dur)
274      (set! (ly:music-property m 'duration)
275       (ly:make-duration l d
276        (* num (car factor))
277        (* denom (cdr factor))))))
278    m))
279
280 % helper routine to set duration.
281 #(define (ac:setduration music duration)
282   "Set a note's duration."
283   (let ((eventtype (ly:music-property music 'name)))
284    (if
285     (or
286      (eq? eventtype 'NoteEvent)
287      (eq? eventtype 'RestEvent)
288      (eq? eventtype 'SkipEvent))
289     (set! (ly:music-property music 'duration) duration))))
290
291 % Add an articulation event to a note.
292 % Used in afterGrace to mark all notes as tenuto, so they're not shortened
293 #(define (ac:add-articulation type music)
294     (music-map (lambda (m)
295                 (if (eq? 'EventChord (ly:music-property m 'name))
296                  (set! (ly:music-property m 'elements)
297                   (append (ly:music-property m 'elements)
298                    (list (make-music 'ArticulationEvent 'articulation-type type)))))
299                 m)
300      music))
301
302 % Convert a long note to an equivalent set of short notes, tied together.
303 % This is needed to get smooth dynamics changes.
304 % Need to deal properly with stuff other than the notes (dynamics, markup etc)
305 % Still experimental, so disabled for now.
306 #(define (ac:to128 music) music)
307
308 #(define (ac:to128_disabled music)
309   (if (or (eq? 'SkipEvent (ly:music-property music 'name))
310         (eq? 'NoteEvent (ly:music-property music 'name)))
311    (let* ((dur (ly:music-property music 'duration))
312           (log2 (ly:duration-log dur))
313          (shiftcount (- 6 log2))
314          (lastm (ly:music-deep-copy (shift-duration-log music shiftcount 0))))
315    (set! (ly:music-property music 'elements)
316     (cons (make-music 'TieEvent) (ly:music-property music 'elements)))
317    (make-sequential-music (list
318                            (make-repeat "unfold" (1- (expt 2 shiftcount))
319                             (make-sequential-music (list music)) '())
320                            lastm)))
321  music))
322
323
324 % absolute time in minutes of a length of music, as a rational number (moment)
325 #(define (ac:abstime music)
326   (ly:moment-div (ly:music-length music) ac:currentTempo))
327
328 % convert absolute time (in minutes) to a moment in the current tempo
329 #(define (ac:abs->mom m)
330   (ly:moment-mul m ac:currentTempo))
331
332
333 % a moment that is ac:maxTwiddletime seconds at the current tempo.
334 #(define (ac:targetTwiddleTime)
335   (ac:abs->mom ac:maxTwiddleTime))
336
337
338 % Nearest twiddletime (in minutes) achievable with power-of-2 divisions of
339 % the original music.  (twiddletime is the time for one pair of notes
340 % in a trill)
341 % If the music has a precomputed twiddletime (e.g., from \afterGrace) use that.
342 #(define (ac:twiddletime music)
343   (let* ((tr (filter (lambda (x)
344                      (and (eq? 'ArticulationEvent (ly:music-property x 'name))
345                       (string= "trill" (ly:music-property x 'articulation-type))))
346               (ly:music-property music 'elements)))
347          (pre-t (if (pair? tr) (ly:music-property (car tr) 'twiddle)
348                  '()))
349          (t (ac:targetTwiddleTime)))
350    (if (ly:moment? pre-t)
351     pre-t
352     (let loop ((len (ly:music-length music)))
353      (if (ly:moment<? t len)
354       (loop (ly:moment-mul len (ly:make-moment 1 2)))
355       len)))))
356
357
358
359 % Note: I'm assuming early music practice of starting on the auxiliary note.
360 % Needs to add gruppetto if it's a long trill (TODO)
361 #(define (ac:trill music)
362   " Replace music with time-compressed repeats of the music,
363     maybe accelerating if the length is longer than a crotchet "
364   (let* ((hemisemidur (ly:make-duration 5 0 1 1))
365          (orig-len  (ly:music-length music))
366          (t (ac:twiddletime music))
367          (uppernote '())
368          (note_moment (ly:moment-mul t (ly:make-moment 1 2)))
369          (c1 (ly:moment-div orig-len note_moment))
370          (c2 (inexact->exact
371               (round (/ (ly:moment-main-numerator c1)
372                       (* 2 (ly:moment-main-denominator c1))))))
373          (count (if (< c2 2) 2 c2)))
374
375    (set! (ly:music-property music 'elements)
376     (filter (lambda (y) (eq? 'NoteEvent (ly:music-property y 'name)))
377      (ly:music-property music 'elements)))
378    (map (lambda (y) (ac:setduration y hemisemidur))
379     (ly:music-property music 'elements))
380    (set! uppernote (ly:music-deep-copy music))
381    (map (lambda (y) (ac:up y))
382     (filter
383      (lambda (z) (eq? 'NoteEvent (ly:music-property z 'name)))
384      (ly:music-property uppernote 'elements)))
385
386    (let* ((trillMusicElements
387           (let loop ((so_far (list uppernote music))
388                      (c count))
389            (if (> c 1)
390             (loop (append (list (ly:music-deep-copy uppernote) (ly:music-deep-copy music)) so_far) (1- c))
391             so_far)))
392           (trillMusic (make-sequential-music trillMusicElements))
393           (newlen (ly:music-length trillMusic))
394           (factor (ly:moment-div  orig-len newlen)))
395     (ly:music-compress trillMusic factor)
396 ; accelerating the music seems to put lily into an infinite loop in
397 ; its layout and midi engines.
398 ;    (let* ((realfactor (exp (* (/ 1.0 count) (log 0.75))))
399 ;          (factor (ly:make-moment (inexact->exact (round (* 1024 realfactor)))
400 ;                   1024)))
401 ;     (ac:accel trillMusic factor))
402  )))
403
404 %
405 % Generate a tempoChangeEvent and its associated property setting.
406 %
407 #(define (ac:tempoChange tempo)
408   (make-sequential-music
409    (list (make-music 'TempoChangeEvent
410           'metronome-count
411           tempo
412           'tempo-unit
413           (ly:make-duration 0 0 1 1))
414     (context-spec-music
415     (make-property-set 'tempoWholesPerMinute  tempo) 'Score))))
416
417 %
418 % Totally unfold repeats, so that the non-obvious sequencing doesn't
419 % confuse us.  This is necessary for time stealing to work, because
420 % that relies on the sequence in which we see events matching their
421 % audible sequence.  Also unfold multi-measure rests to equivalent
422 % skips, with preceding and following bar checks, so that time stealing
423 % can change the length of the pause without falling foul of the
424 % implicit bar checks.
425 %
426 #(define (ac:unfoldMusic music)
427   (music-map
428    (lambda (m)
429     (case (ly:music-property m 'name)
430      ((UnfoldedRepeatedMusic)
431       (let
432        ((body (ly:music-property m 'element))
433         (altl (ly:music-property m 'elements))
434         (rc (ly:music-property m 'repeat-count)))
435        (if (null? altl)
436         (make-sequential-music
437          (list-tabulate rc (lambda (i) (ly:music-deep-copy body))))
438         (let ((ealtl (if (> (length altl) rc) (take altl rc) altl)))
439          (make-sequential-music
440           (apply append!
441            (append!
442             (list-tabulate
443              (- rc (length ealtl))
444              (lambda (i) (list (ly:music-deep-copy body) (ly:music-deep-copy (car ealtl)))))
445             (map (lambda (alt) (list (ly:music-deep-copy body) alt))))))))))
446      ((MultiMeasureRestMusic)
447       (make-sequential-music
448        (list
449         (make-music 'BarCheck)
450         (make-music 'SkipMusic 'duration (ly:music-property m 'duration))
451         (make-music 'BarCheck))))
452      (else
453       m)))
454    (unfold-repeats music)))
455
456 % If there's an articulation, use it.
457 % If in a slur, use (1 . 1) instead.
458 % Treat phrasing slurs as slurs, but allow explicit articulation.
459 % (Maybe should treat staccato under a phrasing slur as mezzo-staccato?)
460 %
461 % Expect an EventChord.
462 %
463 % trills, turns, ornaments etc.  are also treated as Articulations.
464 % Split into two functions:
465 %  ac:getactions traverses the elements in the EventChord
466 %               and calculates the parameters.
467 %  ac:articulate-chord applies the actions to each NoteEvent in
468 %               the EventChord.
469 #(define (ac:getactions music)
470   (let  loop ((factor ac:normalFactor)
471               (newelements '())
472               (es (ly:music-property music 'elements))
473               (actions '()))
474    (if (null? es)
475     (begin
476      (set! (ly:music-property music 'elements) (reverse newelements))
477      (if
478       (not (any (lambda (m) (music-is-of-type? m 'rhythmic-event))
479                 newelements))
480       actions
481       (append
482        (let ((st ac:stealForward))
483         (if (= st 0)
484          '()
485          (begin
486           (set! ac:stealForward 0)
487           (list 'steal st))))
488        actions
489        (cond
490         (ac:inTrill '(trill))
491         ((and (eq? factor ac:normalFactor) (or ac:inSlur ac:inPhrasingSlur))
492          (list 'articulation  '(1 . 1)))
493         (else (list 'articulation  factor))))))
494     ; else part
495     (let ((e (car es))
496           (tail (cdr es)))
497      (case (ly:music-property e 'name)
498
499       ((BeamEvent) ; throw away beam events, or they'll be duplicated by turn or trill
500        (loop factor newelements tail actions))
501
502       ((LineBreakEvent FingeringEvent MarkEvent BreathingEvent TieEvent SkipEvent RestEvent) ; pass through some events.
503        (loop (cons 1 1) (cons e newelements) tail actions))
504
505       ((ArticulationEvent)
506        (let ((articname (ly:music-property e 'articulation-type)))
507         ; TODO: add more here
508         (cond
509          ((string= articname "staccato")
510           (loop ac:staccatoFactor newelements tail actions))
511          ((string= articname "staccatissimo")
512           (loop ac:staccatissimoFactor newelements tail actions))
513          ((string= articname "tenuto")
514           (loop ac:tenutoFactor newelements tail actions))
515          ((string= articname "mordent")
516           (loop (cons 1 1) newelements tail (cons 'mordent actions)))
517          ((string= articname "prall")
518           (loop (cons 1 1) newelements tail (cons 'prall actions)))
519          ((string= articname "trill")
520           (loop (cons 1 1) newelements tail (cons 'trill actions)))
521          ((string= articname "turn")
522           (loop (cons 1 1) newelements tail (cons 'turn actions)))
523          (else (loop factor (cons e newelements) tail actions)))))
524
525       ((TextScriptEvent)
526        (let ((t (ly:music-property e 'text)))
527         (if (not (string? t))
528          (loop factor (cons e newelements) tail actions)
529          (begin
530           (cond
531            ((or
532              (string= t "rall")
533              (string= t "Rall")
534              (string= t "rit.")
535              (string= t "rall."))
536             (loop factor (cons e newelements) tail (cons 'rall actions)))
537            ((or
538              (string= t "accelerando")
539              (string= t "accel")
540              (string= t "accel."))
541             (loop factor (cons e newelements) tail (cons 'accel actions)))
542            ((or
543              (string= t "poco accel."))
544             (loop factor (cons e newelements) tail (cons 'pocoAccel actions)))
545            ((or
546              (string= t "poco rall.")
547              (string= t "poco rit."))
548             (loop factor (cons e newelements) tail (cons 'pocoRall actions)))
549            ((or (string= t "a tempo")
550              (string= t "tempo I"))
551           (loop factor (cons e newelements) tail (cons 'aTempo actions)))
552            (else (loop factor (cons e newelements) tail actions)))))))
553
554       ((SlurEvent)
555        (let ((direction (ly:music-property e 'span-direction)))
556         (set! ac:inSlur (eq? direction -1))
557         (loop factor newelements tail actions)))
558
559       ((TrillSpanEvent)
560        (let ((direction (ly:music-property e 'span-direction)))
561         (set! ac:inTrill (eq? direction -1))
562         (if ac:inTrill
563          (loop factor newelements tail (cons 'trill actions))
564          (loop factor (cons e newelements) tail actions))))
565
566       ((PhrasingSlurEvent)
567        (let ((direction (ly:music-property e 'span-direction)))
568         (set! ac:inPhrasingSlur (eq? direction -1))
569         (loop factor newelements tail actions)))
570
571       (else (loop factor (cons e newelements) tail actions)))))))
572
573
574
575 #(define (ac:articulate-chord music)
576   (cond
577    ((eq? 'EventChord (ly:music-property music 'name))
578     (ac:logEventsBackward
579      (let loop ((actions (ac:getactions music)))
580       (if (null? actions)
581         (if (ly:moment<? (ly:make-moment 1/4) (ly:music-length music))
582          (ac:to128  music)
583          music)
584
585       (case (car actions)
586
587        ((articulation)
588         (map
589          (lambda (x) (ac:articulate-one-note x (cadr actions)))
590          (ly:music-property music 'elements))
591         (let*
592          ((num (caadr actions))
593           (denom (cdadr actions))
594           (mult (ly:duration-factor ac:currentDuration))
595           (newnum (* (- denom num) (car mult)))
596           (newdenom (* (cdr mult) denom))
597           (len (ly:duration-log ac:currentDuration))
598           (dots (ly:duration-dot-count ac:currentDuration)))
599
600          (if (not (eq? num denom))
601           (make-sequential-music
602            (list (ac:to128 music)
603            (make-music 'EventChord 'elements
604             (list
605              (make-music 'RestEvent 'duration (ly:make-duration len dots newnum newdenom))))))
606           music)))
607
608        ((accel)
609         (set! ac:lastTempo ac:currentTempo)
610         (set! ac:currentTempo (ly:moment-div ac:currentTempo ac:rallFactor))
611         (let ((pset (ac:tempoChange ac:currentTempo)))
612          (if (null? (cdr actions))
613           (make-sequential-music (list pset music))
614           (make-sequential-music
615            (list pset (loop (cdr actions)))))))
616
617        ((pocoAccel)
618         (set! ac:lastTempo ac:currentTempo)
619         (set! ac:currentTempo (ly:moment-div ac:currentTempo ac:pocoRallFactor))
620         (let ((pset (ac:tempoChange ac:currentTempo)))
621          (if (null? (cdr actions))
622           (make-sequential-music (list pset music))
623           (make-sequential-music
624            (list pset (loop (cdr actions)))))))
625
626        ((rall)
627         (set! ac:lastTempo ac:currentTempo)
628         (set! ac:currentTempo (ly:moment-mul ac:currentTempo ac:rallFactor))
629         (let ((pset (ac:tempoChange ac:currentTempo)))
630          (if (null? (cdr actions))
631           (make-sequential-music (list pset music))
632           (make-sequential-music
633            (list pset (loop (cdr actions)))))))
634
635        ((pocoRall)
636         (set! ac:lastTempo ac:currentTempo)
637         (set! ac:currentTempo (ly:moment-mul ac:currentTempo ac:pocoRallFactor))
638         (let ((pset (ac:tempoChange ac:currentTempo)))
639          (if (null? (cdr actions))
640           (make-sequential-music (list pset music))
641           (make-sequential-music
642            (list pset (loop (cdr actions)))))))
643
644        ((aTempo)
645         (set! ac:currentTempo ac:lastTempo)
646
647         (let ((pset (ac:tempoChange ac:currentTempo)))
648          (if (null? (cdr actions))
649           (make-sequential-music (list pset music))
650           (make-sequential-music
651            (list pset (loop (cdr actions)))))))
652
653        ((trill)
654          (ac:trill music))
655
656        ((prall)
657         ; A pralltriller symbol can either mean an inverted mordent
658         ; or a half-shake -- a short, two twiddle trill.
659         ; We implement as a half-shake.
660         (let*
661          ((totallength (ly:music-length music))
662           (newlen (ly:moment-sub totallength (ly:make-moment 3 32)))
663           (newdur (ly:make-duration
664                    0 0
665                    (ly:moment-main-numerator newlen)
666                    (ly:moment-main-denominator newlen)))
667           (gracedur (ly:make-duration 5 0 1 1))
668           (gracenote (ly:music-deep-copy music))
669           (abovenote (ly:music-deep-copy music))
670           (mainnote (ly:music-deep-copy music))
671           (prall (make-sequential-music (list gracenote abovenote)))
672         )
673           (music-map (lambda (n)
674            (if (eq? 'NoteEvent (ly:music-property n 'name))
675             (set! (ly:music-property n 'duration) gracedur))
676                       n)
677            abovenote)
678           (music-map (lambda (n)
679            (if (eq? 'NoteEvent (ly:music-property n 'name))
680             (set! (ly:music-property n 'duration) gracedur))
681                       n)
682            gracenote)
683           (music-map (lambda (n)
684            (if (eq? 'NoteEvent (ly:music-property n 'name))
685             (set! (ly:music-property n 'duration) newdur))
686                       n)
687            mainnote)
688
689           (map (lambda (y) (ac:up y))
690            (filter
691             (lambda (z) (eq? 'NoteEvent (ly:music-property z 'name)))
692             (ly:music-property abovenote 'elements)))
693           (make-sequential-music (list abovenote gracenote abovenote mainnote))))
694
695        ((mordent)
696         (let*
697          ((totaldur (ly:music-property
698                 (car (ly:music-property music 'elements)) 'duration))
699           (dur (ly:duration-length totaldur))
700           (newlen (ly:moment-sub dur (ly:make-moment 2 32)))
701           (newdur (ly:make-duration
702                 0 0
703                    (ly:moment-main-numerator newlen)
704                    (ly:moment-main-denominator newlen)))
705           (gracenote (ly:music-deep-copy music))
706           (belownote (ly:music-deep-copy music))
707           (mainnote (ly:music-deep-copy music))
708           (mordent (make-sequential-music (list gracenote belownote)))
709         )
710          (begin
711           (music-map (lambda (n)
712            (if (eq? 'NoteEvent (ly:music-property n 'name))
713             (set! (ly:music-property n 'duration)
714              (ly:make-duration 5 0 1 1)))
715                       n)
716            mordent)
717           (music-map (lambda (n)
718            (if (eq? 'NoteEvent (ly:music-property n 'name))
719             (set! (ly:music-property n 'duration) newdur))
720                       n)
721            mainnote)
722           (map (lambda (y) (ac:down y))
723            (filter
724             (lambda (z) (eq? 'NoteEvent (ly:music-property z 'name)))
725             (ly:music-property belownote 'elements)))
726           (make-sequential-music (list mordent mainnote)))))
727        ((turn)
728         (let*
729          ((dur (ly:music-property
730                 (car (ly:music-property music 'elements)) 'duration))
731           (factor (ly:duration-factor dur))
732           (newdur (ly:make-duration (+ (ly:duration-log dur) 2)
733                    (ly:duration-dot-count dur) (car factor)(cdr factor))))
734          (begin
735           (map (lambda (y) (ac:setduration y newdur))
736            (ly:music-property music 'elements))
737           (let* ((above (ly:music-deep-copy music))
738                  (below (ly:music-deep-copy music))
739                  (newmusic (make-sequential-music (list above music below music))))
740            (begin
741             (map (lambda (y) (ac:down y))
742              (filter
743               (lambda (z) (eq? 'NoteEvent (ly:music-property z 'name)))
744               (ly:music-property below 'elements)))
745             (map (lambda (y) (ac:up y))
746              (filter
747               (lambda (z) (eq? 'NoteEvent (ly:music-property z 'name)))
748               (ly:music-property above 'elements)))
749             newmusic)))))
750        ((steal)
751         (let
752          ((totallen (ly:moment-main (ly:music-length music)))
753           (steallen (cadr actions)))
754          (if (>= steallen totallen)
755           (begin
756            (if (any (lambda (z) (eq? 'NoteEvent (ly:music-property z 'name)))
757                     (ly:music-property music 'elements))
758             (ly:warning (_ "stealing the entirety of a note's time")))
759            (set! ac:stealForward (- steallen totallen))
760            (make-sequential-music '()))
761           (begin
762            (ly:music-compress music (ly:make-moment (/ (- totallen steallen) totallen)))
763            (loop (cddr actions))))))
764      )))))
765
766    ((eq? 'GraceMusic (ly:music-property music 'name))
767     (let
768      ((first-ev
769        (call-with-current-continuation
770         (lambda (yield-fev)
771          (music-map
772           (lambda (m)
773            (if (eq? 'EventChord (ly:music-property m 'name))
774             (yield-fev m)
775             m))
776           music)
777          #f))))
778      (if first-ev
779       (let ((fev-pos (find-tail (lambda (m) (eq? m first-ev)) ac:eventsBackward)))
780        (if fev-pos
781         (set! ac:eventsBackward (cdr fev-pos))
782         (ly:warning (_ "articulation of grace notes has gone awry"))))))
783     (let*
784      ((gmus (ly:music-compress (ly:music-property music 'element)
785                                (ly:make-moment ac:defaultGraceFactor)))
786       (glen (ly:moment-main (ly:music-length gmus))))
787      (ac:stealTimeBackward (* glen ac:defaultGraceBackwardness))
788      (set! ac:stealForward (+ ac:stealForward (* glen (- 1 ac:defaultGraceBackwardness))))
789      gmus))
790
791    ((memq (ly:music-property music 'name) '(BarCheck SkipMusic))
792     (let ((totallen (ly:moment-main (ly:music-length music)))
793           (steallen ac:stealForward))
794      (cond
795       ((= steallen 0)
796        (ac:logEventsBackward music))
797       ((< steallen totallen)
798        (set! ac:stealForward 0)
799        (ac:logEventsBackward
800         (ly:music-compress music (ly:make-moment (/ (- totallen steallen) totallen)))))
801       (else
802        (set! ac:stealForward (- steallen totallen))
803        (make-sequential-music '())))))
804
805    ((eq? 'KeyChangeEvent (ly:music-property music 'name))
806     (set! ac:current-key music)
807     music)
808
809    ((eq? 'PropertySet (ly:music-property music 'name))
810     (ac:adjust-props (ly:music-property music 'symbol) music)
811     music)
812
813    (else music)))
814
815
816
817 % At last ... here's the music function that applies all the above to a
818 % score.
819 articulate = #(define-music-function (parser location music)
820                (ly:music?)
821                "Adjust times of note to add tenuto, staccato and
822                 normal articulations.
823                 "
824                (dynamic-wind
825                 (lambda ()
826                  (set! ac:stealForward 0)
827                  (set! ac:eventsBackward '()))
828                 (lambda ()
829                  (music-map
830                   ac:articulate-chord
831                   (event-chord-wrap! (ac:unfoldMusic music) parser)))
832                 (lambda ()
833                  (or (= ac:stealForward 0)
834                   (begin
835                    (ly:warning (_ "articulation failed to steal ~a note at end of music") ac:stealForward)
836                    (set! ac:stealForward 0)))
837                  (set! ac:eventsBackward '()))))
838
839
840 % Override \afterGrace to be in terms of audio, not spacing.
841 % Special handling for a gruppetto after a trill.
842 afterGrace =
843 #(define-music-function
844   (parser location main grace)
845   (ly:music? ly:music?)
846
847   (set! main (event-chord-wrap! main parser))
848   (set! grace (event-chord-wrap! grace parser))
849   (let*
850    ((main-length (ly:music-length main))
851     (grace-orig-length (ly:music-length grace))
852     (gracelen (ac:twiddletime main))
853     (grace-factor (ly:moment-div gracelen grace-orig-length))
854     (new-main-length (ly:moment-sub main-length gracelen))
855     (factor (ly:moment-div new-main-length main-length))
856   )
857    (map (lambda (y) (set! (ly:music-property y 'twiddle) gracelen))
858          (filter (lambda (z)
859                   (and
860                    (eq? 'ArticulationEvent (ly:music-property z 'name))
861                    (string= "trill" (ly:music-property z 'articulation-type))))
862           (ly:music-property main 'elements)))
863    (ac:add-articulation "tenuto" grace)
864    (make-sequential-music  (list (ly:music-compress main factor) (ly:music-compress grace grace-factor)))))
865
866 % An appoggiatura takes half the duration of the main note,
867 % or 1/3 if the note is dotted (i.e., half the undotted equivalent time)
868 % Somewhere around the end of the 19th, start of 20th century the rules
869 % changed, but my main interest is early music.
870 appoggiatura =
871 #(define-music-function (parser location grace main)
872   (ly:music? ly:music?)
873   (set! grace (event-chord-wrap! grace parser))
874   (set! main (event-chord-wrap! main parser))
875   (let* ((maindur (ly:music-length main))
876          (grace-orig-len (ly:music-length grace))
877          (main-orig-len (ly:music-length main))
878          (numerator (ly:moment-main-numerator maindur))
879          (factor (if (eq? (remainder numerator 3) 0)
880                   (ly:make-moment 1 3) (ly:make-moment 1 2))))
881    (ly:music-compress grace
882     (ly:moment-mul factor (ly:moment-div main-orig-len grace-orig-len)))
883    (ly:music-compress main (ly:moment-sub (ly:make-moment 1 1) factor))
884
885     (set! (ly:music-property grace 'elements)
886      (append (ly:music-property grace 'elements)
887       (list (make-music 'SlurEvent 'span-direction -1))))
888     (set! (ly:music-property main 'elements)
889      (append (ly:music-property main 'elements)
890       (list (make-music 'SlurEvent 'span-direction 1))))
891      (make-sequential-music (list grace main))))
892