]> git.donarmstrong.com Git - lilypond.git/blob - scm/music-functions.scm
Merge branch 'lilypond/translation' of ssh://git.sv.gnu.org/srv/git/lilypond into...
[lilypond.git] / scm / music-functions.scm
1 ;;;; This file is part of LilyPond, the GNU music typesetter.
2 ;;;;
3 ;;;; Copyright (C) 1998--2012 Jan Nieuwenhuizen <janneke@gnu.org>
4 ;;;;                 Han-Wen Nienhuys <hanwen@xs4all.nl>
5 ;;;;
6 ;;;; LilyPond is free software: you can redistribute it and/or modify
7 ;;;; it under the terms of the GNU General Public License as published by
8 ;;;; the Free Software Foundation, either version 3 of the License, or
9 ;;;; (at your option) any later version.
10 ;;;;
11 ;;;; LilyPond is distributed in the hope that it will be useful,
12 ;;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
13 ;;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14 ;;;; GNU General Public License for more details.
15 ;;;;
16 ;;;; You should have received a copy of the GNU General Public License
17 ;;;; along with LilyPond.  If not, see <http://www.gnu.org/licenses/>.
18
19 ; for define-safe-public when byte-compiling using Guile V2
20 (use-modules (scm safe-utility-defs))
21
22 (use-modules (ice-9 optargs))
23
24 ;;; ly:music-property with setter
25 ;;; (ly:music-property my-music 'elements)
26 ;;;   ==> the 'elements property
27 ;;; (set! (ly:music-property my-music 'elements) value)
28 ;;;   ==> set the 'elements property and return it
29 (define-public ly:music-property
30   (make-procedure-with-setter ly:music-property
31                               ly:music-set-property!))
32
33 (define-safe-public (music-is-of-type? mus type)
34   "Does @code{mus} belong to the music class @code{type}?"
35   (memq type (ly:music-property mus 'types)))
36
37 ;; TODO move this
38 (define-public ly:grob-property
39   (make-procedure-with-setter ly:grob-property
40                               ly:grob-set-property!))
41
42 (define-public ly:grob-object
43   (make-procedure-with-setter ly:grob-object
44                               ly:grob-set-object!))
45
46 (define-public ly:grob-parent
47   (make-procedure-with-setter ly:grob-parent
48                               ly:grob-set-parent!))
49
50 (define-public ly:prob-property
51   (make-procedure-with-setter ly:prob-property
52                               ly:prob-set-property!))
53
54 (define-public ly:context-property
55   (make-procedure-with-setter ly:context-property
56                               ly:context-set-property!))
57
58 (define-public (music-map function music)
59   "Apply @var{function} to @var{music} and all of the music it contains.
60
61 First it recurses over the children, then the function is applied to
62 @var{music}."
63   (let ((es (ly:music-property music 'elements))
64         (e (ly:music-property music 'element)))
65     (if (pair? es)
66         (set! (ly:music-property music 'elements)
67               (map (lambda (y) (music-map function y)) es)))
68     (if (ly:music? e)
69         (set! (ly:music-property music 'element)
70               (music-map function  e)))
71     (function music)))
72
73 (define-public (music-filter pred? music)
74   "Filter out music expressions that do not satisfy @var{pred?}."
75
76   (define (inner-music-filter pred? music)
77     "Recursive function."
78     (let* ((es (ly:music-property music 'elements))
79            (e (ly:music-property music 'element))
80            (as (ly:music-property music 'articulations))
81            (filtered-as (filter ly:music? (map (lambda (y) (inner-music-filter pred? y)) as)))
82            (filtered-e (if (ly:music? e)
83                            (inner-music-filter pred? e)
84                            e))
85            (filtered-es (filter ly:music? (map (lambda (y) (inner-music-filter pred? y)) es))))
86       (if (not (null? e))
87           (set! (ly:music-property music 'element) filtered-e))
88       (if (not (null? es))
89           (set! (ly:music-property music 'elements) filtered-es))
90       (if (not (null? as))
91           (set! (ly:music-property music 'articulations) filtered-as))
92       ;; if filtering emptied the expression, we remove it completely.
93       (if (or (not (pred? music))
94               (and (eq? filtered-es '()) (not (ly:music? e))
95                    (or (not (eq? es '()))
96                        (ly:music? e))))
97           (set! music '()))
98       music))
99
100   (set! music (inner-music-filter pred? music))
101   (if (ly:music? music)
102       music
103       (make-music 'Music)))       ;must return music.
104
105 (define*-public (display-music music #:optional (port (current-output-port)))
106   "Display music, not done with @code{music-map} for clarity of
107 presentation."
108   (display music port)
109   (display ": { " port)
110   (let ((es (ly:music-property music 'elements))
111         (e (ly:music-property music 'element)))
112     (display (ly:music-mutable-properties music) port)
113     (if (pair? es)
114         (begin (display "\nElements: {\n" port)
115                (for-each (lambda (m) (display-music m port)) es)
116                (display "}\n" port)))
117     (if (ly:music? e)
118         (begin
119           (display "\nChild:" port)
120           (display-music e port))))
121   (display " }\n" port)
122   music)
123
124 ;;;
125 ;;; A scheme music pretty printer
126 ;;;
127 (define (markup-expression->make-markup markup-expression)
128   "Transform `markup-expression' into an equivalent, hopefuly readable, scheme expression.
129 For instance,
130   \\markup \\bold \\italic hello
131 ==>
132   (markup #:line (#:bold (#:italic (#:simple \"hello\"))))"
133   (define (proc->command-keyword proc)
134     "Return a keyword, eg. `#:bold', from the `proc' function, eg. #<procedure bold-markup (layout props arg)>"
135     (let ((cmd-markup (symbol->string (procedure-name proc))))
136       (symbol->keyword (string->symbol (substring cmd-markup 0 (- (string-length cmd-markup)
137                                                                   (string-length "-markup")))))))
138   (define (transform-arg arg)
139     (cond ((and (pair? arg) (markup? (car arg))) ;; a markup list
140            (apply append (map inner-markup->make-markup arg)))
141           ((and (not (string? arg)) (markup? arg)) ;; a markup
142            (inner-markup->make-markup arg))
143           (else                                  ;; scheme arg
144            (music->make-music arg))))
145   (define (inner-markup->make-markup mrkup)
146     (if (string? mrkup)
147         `(#:simple ,mrkup)
148         (let ((cmd (proc->command-keyword (car mrkup)))
149               (args (map transform-arg (cdr mrkup))))
150           `(,cmd ,@args))))
151   ;; body:
152   (if (string? markup-expression)
153       markup-expression
154       `(markup ,@(inner-markup->make-markup markup-expression))))
155
156 (define-public (music->make-music obj)
157   "Generate an expression that, once evaluated, may return an object
158 equivalent to @var{obj}, that is, for a music expression, a
159 @code{(make-music ...)} form."
160   (cond (;; markup expression
161          (markup? obj)
162          (markup-expression->make-markup obj))
163         (;; music expression
164          (ly:music? obj)
165          `(make-music
166            ',(ly:music-property obj 'name)
167            ,@(apply append (map (lambda (prop)
168                                   `(',(car prop)
169                                     ,(music->make-music (cdr prop))))
170                                 (remove (lambda (prop)
171                                           (eqv? (car prop) 'origin))
172                                         (ly:music-mutable-properties obj))))))
173         (;; moment
174          (ly:moment? obj)
175          `(ly:make-moment ,(ly:moment-main-numerator obj)
176                           ,(ly:moment-main-denominator obj)
177                           ,(ly:moment-grace-numerator obj)
178                           ,(ly:moment-grace-denominator obj)))
179         (;; note duration
180          (ly:duration? obj)
181          `(ly:make-duration ,(ly:duration-log obj)
182                             ,(ly:duration-dot-count obj)
183                             ,(car (ly:duration-factor obj))
184                             ,(cdr (ly:duration-factor obj))))
185         (;; note pitch
186          (ly:pitch? obj)
187          `(ly:make-pitch ,(ly:pitch-octave obj)
188                          ,(ly:pitch-notename obj)
189                          ,(ly:pitch-alteration obj)))
190         (;; scheme procedure
191          (procedure? obj)
192          (or (procedure-name obj) obj))
193         (;; a symbol (avoid having an unquoted symbol)
194          (symbol? obj)
195          `',obj)
196         (;; an empty list (avoid having an unquoted empty list)
197          (null? obj)
198          `'())
199         (;; a proper list
200          (list? obj)
201          `(list ,@(map music->make-music obj)))
202         (;; a pair
203          (pair? obj)
204          `(cons ,(music->make-music (car obj))
205                 ,(music->make-music (cdr obj))))
206         (else
207          obj)))
208
209 (use-modules (ice-9 pretty-print))
210 (define*-public (display-scheme-music obj #:optional (port (current-output-port)))
211   "Displays `obj', typically a music expression, in a friendly fashion,
212 which often can be read back in order to generate an equivalent expression."
213   (pretty-print (music->make-music obj) port)
214   (newline port))
215
216 ;;;
217 ;;; Scheme music expression --> Lily-syntax-using string translator
218 ;;;
219 (use-modules (srfi srfi-39)
220              (scm display-lily))
221
222 (define*-public (display-lily-music expr parser #:optional (port (current-output-port))
223                                     #:key force-duration)
224   "Display the music expression using LilyPond syntax"
225   (memoize-clef-names supported-clefs)
226   (parameterize ((*indent* 0)
227                  (*previous-duration* (ly:make-duration 2))
228                  (*force-duration* force-duration))
229     (display (music->lily-string expr parser) port)
230     (newline port)))
231
232 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
233
234 (define-public (shift-one-duration-log music shift dot)
235   "Add @var{shift} to @code{duration-log} of @code{'duration} in
236 @var{music} and optionally @var{dot} to any note encountered.
237 The number of dots in the shifted music may not be less than zero."
238   (let ((d (ly:music-property music 'duration)))
239     (if (ly:duration? d)
240         (let* ((cp (ly:duration-factor d))
241                (nd (ly:make-duration
242                     (+ shift (ly:duration-log d))
243                     (max 0 (+ dot (ly:duration-dot-count d)))
244                     (car cp)
245                     (cdr cp))))
246           (set! (ly:music-property music 'duration) nd)))
247     music))
248
249 (define-public (shift-duration-log music shift dot)
250   (music-map (lambda (x) (shift-one-duration-log x shift dot))
251              music))
252
253 (define-public (make-repeat name times main alts)
254   "Create a repeat music expression, with all properties initialized
255 properly."
256   (define (first-note-duration music)
257     "Finds the duration of the first NoteEvent by searching depth-first
258 through MUSIC."
259     ;; NoteEvent or a non-expanded chord-repetition
260     ;; We just take anything that actually sports an announced duration.
261     (if (ly:duration? (ly:music-property music 'duration))
262         (ly:music-property music 'duration)
263         (let loop ((elts (if (ly:music? (ly:music-property music 'element))
264                              (list (ly:music-property music 'element))
265                              (ly:music-property music 'elements))))
266           (and (pair? elts)
267                (let ((dur (first-note-duration (car elts))))
268                  (if (ly:duration? dur)
269                      dur
270                      (loop (cdr elts))))))))
271
272   (let ((talts (if (< times (length alts))
273                    (begin
274                      (ly:warning (_ "More alternatives than repeats.  Junking excess alternatives"))
275                      (take alts times))
276                    alts))
277         (r (make-repeated-music name)))
278     (set! (ly:music-property r 'element) main)
279     (set! (ly:music-property r 'repeat-count) (max times 1))
280     (set! (ly:music-property r 'elements) talts)
281     (if (and (equal? name "tremolo")
282              (pair? (extract-named-music main '(EventChord NoteEvent))))
283         ;; This works for single-note and multi-note tremolos!
284         (let* ((children (if (music-is-of-type? main 'sequential-music)
285                              ;; \repeat tremolo n { ... }
286                              (length (extract-named-music main '(EventChord
287                                                                  NoteEvent)))
288                              ;; \repeat tremolo n c4
289                              1))
290                ;; # of dots is equal to the 1 in bitwise representation (minus 1)!
291                (dots (1- (logcount (* times children))))
292                ;; The remaining missing multiplicator to scale the notes by
293                ;; times * children
294                (mult (/ (* times children (ash 1 dots)) (1- (ash 2 dots))))
295                (shift (- (ly:intlog2 (floor mult))))
296                (note-duration (first-note-duration r))
297                (duration-log (if (ly:duration? note-duration)
298                                  (ly:duration-log note-duration)
299                                  1))
300                (tremolo-type (ash 1 duration-log)))
301           (set! (ly:music-property r 'tremolo-type) tremolo-type)
302           (if (not (integer?  mult))
303               (ly:warning (_ "invalid tremolo repeat count: ~a") times))
304           ;; Adjust the time of the notes
305           (ly:music-compress r (ly:make-moment 1 children))
306           ;; Adjust the displayed note durations
307           (shift-duration-log r shift dots))
308         r)))
309
310 (define (calc-repeat-slash-count music)
311   "Given the child-list @var{music} in @code{PercentRepeatMusic},
312 calculate the number of slashes based on the durations.  Returns @code{0}
313 if durations in @var{music} vary, allowing slash beats and double-percent
314 beats to be distinguished."
315   (let* ((durs (map duration-of-note
316                     (extract-named-music music '(EventChord NoteEvent
317                                                  RestEvent SkipEvent))))
318          (first-dur (car durs)))
319
320     (if (every (lambda (d) (equal? d first-dur)) durs)
321         (max (- (ly:duration-log first-dur) 2) 1)
322         0)))
323
324 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
325 ;; clusters.
326
327 (define-public (note-to-cluster music)
328   "Replace @code{NoteEvents} by @code{ClusterNoteEvents}."
329   (if (eq? (ly:music-property music 'name) 'NoteEvent)
330       (make-music 'ClusterNoteEvent
331                   'pitch (ly:music-property music 'pitch)
332                   'duration (ly:music-property music 'duration))
333       music))
334
335 (define-public (notes-to-clusters music)
336   (music-map note-to-cluster music))
337
338 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
339 ;; repeats.
340
341 (define-public (unfold-repeats music)
342   "Replace all repeats with unfolded repeats."
343
344   (let ((es (ly:music-property music 'elements))
345         (e (ly:music-property music 'element)))
346
347     (if (memq 'repeated-music (ly:music-property music 'types))
348         (let* ((props (ly:music-mutable-properties music))
349                (old-name (ly:music-property music 'name))
350                (flattened (flatten-alist props)))
351           (set! music (apply make-music (cons 'UnfoldedRepeatedMusic
352                                               flattened)))
353
354           (if (equal? old-name 'TremoloRepeatedMusic)
355               (let* ((seq-arg? (memq 'sequential-music
356                                      (ly:music-property e 'types)))
357                      (count (ly:music-property music 'repeat-count))
358                      (dot-shift (if (= 0 (remainder count 3))
359                                     -1 0))
360                      (child-count (if seq-arg?
361                                       (length (ly:music-property e 'elements))
362                                       0)))
363
364                 (if (= 0 -1)
365                     (set! count (* 2 (quotient count 3))))
366
367                 (shift-duration-log music (+ (if (= 2 child-count)
368                                                  1 0)
369                                              (ly:intlog2 count)) dot-shift)
370
371                 (if seq-arg?
372                     (ly:music-compress e (ly:make-moment child-count 1)))))))
373
374     (if (pair? es)
375         (set! (ly:music-property music 'elements)
376               (map unfold-repeats es)))
377     (if (ly:music? e)
378         (set! (ly:music-property music 'element)
379               (unfold-repeats e)))
380     music))
381
382 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
383 ;; property setting music objs.
384
385 (define-public (make-grob-property-set grob gprop val)
386   "Make a @code{Music} expression that sets @var{gprop} to @var{val} in
387 @var{grob}.  Does a pop first, i.e., this is not an override."
388   (make-music 'OverrideProperty
389               'symbol grob
390               'grob-property gprop
391               'grob-value val
392               'pop-first #t))
393
394 (define-public (make-grob-property-override grob gprop val)
395   "Make a @code{Music} expression that overrides @var{gprop} to @var{val}
396 in @var{grob}."
397   (make-music 'OverrideProperty
398               'symbol grob
399               'grob-property gprop
400               'grob-value val))
401
402 (define-public (make-grob-property-revert grob gprop)
403   "Revert the grob property @var{gprop} for @var{grob}."
404   (make-music 'RevertProperty
405               'symbol grob
406               'grob-property gprop))
407
408 (define direction-polyphonic-grobs
409   '(AccidentalSuggestion
410     DotColumn
411     Dots
412     Fingering
413     LaissezVibrerTie
414     LigatureBracket
415     PhrasingSlur
416     RepeatTie
417     Rest
418     Script
419     Slur
420     Stem
421     TextScript
422     Tie
423     TupletBracket
424     TrillSpanner))
425
426 (define-safe-public (make-voice-props-set n)
427   (make-sequential-music
428    (append
429     (map (lambda (x) (make-grob-property-override x 'direction
430                                                   (if (odd? n) -1 1)))
431          direction-polyphonic-grobs)
432     (list
433      (make-property-set 'graceSettings
434                         ;; TODO: take this from voicedGraceSettings or similar.
435                         '((Voice Stem font-size -3)
436                           (Voice Flag font-size -3)
437                           (Voice NoteHead font-size -3)
438                           (Voice TabNoteHead font-size -4)
439                           (Voice Dots font-size -3)
440                           (Voice Stem length-fraction 0.8)
441                           (Voice Stem no-stem-extend #t)
442                           (Voice Beam beam-thickness 0.384)
443                           (Voice Beam length-fraction 0.8)
444                           (Voice Accidental font-size -4)
445                           (Voice AccidentalCautionary font-size -4)
446                           (Voice Script font-size -3)
447                           (Voice Fingering font-size -8)
448                           (Voice StringNumber font-size -8)))
449
450      (make-grob-property-override 'NoteColumn 'horizontal-shift (quotient n 2))
451      (make-grob-property-override 'MultiMeasureRest 'staff-position (if (odd? n) -4 4))))))
452
453 (define-safe-public (make-voice-props-revert)
454   (make-sequential-music
455    (append
456     (map (lambda (x) (make-grob-property-revert x 'direction))
457          direction-polyphonic-grobs)
458     (list (make-property-unset 'graceSettings)
459           (make-grob-property-revert 'NoteColumn 'horizontal-shift)
460           (make-grob-property-revert 'MultiMeasureRest 'staff-position)))))
461
462
463 (define-safe-public (context-spec-music m context #:optional id)
464   "Add \\context CONTEXT = ID to M."
465   (let ((cm (make-music 'ContextSpeccedMusic
466                         'element m
467                         'context-type context)))
468     (if (string? id)
469         (set! (ly:music-property cm 'context-id) id))
470     cm))
471
472 (define-public (descend-to-context m context)
473   "Like @code{context-spec-music}, but only descending."
474   (let ((cm (context-spec-music m context)))
475     (ly:music-set-property! cm 'descend-only #t)
476     cm))
477
478 (define-public (make-non-relative-music mus)
479   (make-music 'UnrelativableMusic
480               'element mus))
481
482 (define-public (make-apply-context func)
483   (make-music 'ApplyContext
484               'procedure func))
485
486 (define-public (make-sequential-music elts)
487   (make-music 'SequentialMusic
488               'elements elts))
489
490 (define-public (make-simultaneous-music elts)
491   (make-music 'SimultaneousMusic
492               'elements elts))
493
494 (define-safe-public (make-event-chord elts)
495   (make-music 'EventChord
496               'elements elts))
497
498 (define-public (make-skip-music dur)
499   (make-music 'SkipMusic
500               'duration dur))
501
502 (define-public (make-grace-music music)
503   (make-music 'GraceMusic
504               'element music))
505
506 ;;;;;;;;;;;;;;;;
507
508 ;; mmrest
509 (define-public (make-multi-measure-rest duration location)
510   (make-music 'MultiMeasureRestMusic
511               'origin location
512               'duration duration))
513
514 (define-public (make-property-set sym val)
515   (make-music 'PropertySet
516               'symbol sym
517               'value val))
518
519 (define-public (make-property-unset sym)
520   (make-music 'PropertyUnset
521               'symbol sym))
522
523 (define-safe-public (make-articulation name)
524   (make-music 'ArticulationEvent
525               'articulation-type name))
526
527 (define-public (make-lyric-event string duration)
528   (make-music 'LyricEvent
529               'duration duration
530               'text string))
531
532 (define-safe-public (make-span-event type span-dir)
533   (make-music type
534               'span-direction span-dir))
535
536 (define-public (override-head-style heads style)
537   "Override style for @var{heads} to @var{style}."
538   (make-sequential-music
539     (if (pair? heads)
540         (map (lambda (h)
541               (make-grob-property-override h 'style style))
542          heads)
543         (list (make-grob-property-override heads 'style style)))))
544
545 (define-public (revert-head-style heads)
546   "Revert style for @var{heads}."
547   (make-sequential-music
548     (if (pair? heads)
549         (map (lambda (h)
550               (make-grob-property-revert h 'style))
551          heads)
552         (list (make-grob-property-revert heads 'style)))))
553
554 (define-public (style-note-heads heads style music)
555  "Set @var{style} for all @var{heads} in @var{music}.  Works both
556 inside of and outside of chord construct."
557   ;; are we inside a <...>?
558   (if (eq? (ly:music-property music 'name) 'NoteEvent)
559       ;; yes -> use a tweak
560       (begin
561         (set! (ly:music-property music 'tweaks)
562               (acons 'style style (ly:music-property music 'tweaks)))
563         music)
564       ;; not in <...>, so use overrides
565       (make-sequential-music
566         (list
567           (override-head-style heads style)
568           music
569           (revert-head-style heads)))))
570
571  (define-public (set-mus-properties! m alist)
572   "Set all of @var{alist} as properties of @var{m}."
573   (if (pair? alist)
574       (begin
575         (set! (ly:music-property m (caar alist)) (cdar alist))
576         (set-mus-properties! m (cdr alist)))))
577
578 (define-public (music-separator? m)
579   "Is @var{m} a separator?"
580   (let ((ts (ly:music-property m 'types)))
581     (memq 'separator ts)))
582
583 ;;; expanding repeat chords
584 (define-public (copy-repeat-chord original-chord repeat-chord duration
585                                   event-types)
586   "Copies all events in @var{event-types} (be sure to include
587 @code{rhythmic-events}) from @var{original-chord} over to
588 @var{repeat-chord} with their articulations filtered as well.  Any
589 duration is replaced with the specified @var{duration}."
590   ;; First remove everything from event-types that can already be
591   ;; found in the repeated chord.  We don't need to look for
592   ;; articulations on individual events since they can't actually get
593   ;; into a repeat chord given its input syntax.
594   (for-each (lambda (e)
595               (for-each (lambda (x)
596                           (set! event-types (delq x event-types)))
597                         (ly:music-property e 'types)))
598             (ly:music-property repeat-chord 'elements))
599   ;; now treat the elements
600   (set! (ly:music-property repeat-chord 'elements)
601         (append!
602          (filter-map
603           (lambda (m)
604             (and (any (lambda (t) (music-is-of-type? m t)) event-types)
605                  (begin
606                    (set! m (ly:music-deep-copy m))
607                    (if (pair? (ly:music-property m 'articulations))
608                        (set! (ly:music-property m 'articulations)
609                              (filter
610                               (lambda (a)
611                                 (any (lambda (t) (music-is-of-type? a t))
612                                      event-types))
613                               (ly:music-property m 'articulations))))
614                    (if (ly:duration? (ly:music-property m 'duration))
615                        (set! (ly:music-property m 'duration) duration))
616                    m)))
617           (ly:music-property original-chord 'elements))
618          (ly:music-property repeat-chord 'elements))))
619
620 (define-public (expand-repeat-chords! event-types music)
621   "Walks through @var{music} and fills repeated chords (notable by
622 having a duration in @code{duration}) with the notes from their
623 respective predecessor chord."
624   (let loop ((music music) (last-chord #f))
625     (if (music-is-of-type? music 'event-chord)
626         (let ((chord-repeat (ly:music-property music 'duration)))
627           (cond
628            ((not (ly:duration? chord-repeat))
629             music)
630            (last-chord
631             (set! (ly:music-property music 'duration) '())
632             (copy-repeat-chord last-chord music chord-repeat event-types)
633             music)
634            (else
635             (ly:music-warning music (_ "Bad chord repetition"))
636             #f)))
637         (let ((elt (ly:music-property music 'element)))
638           (fold loop (if (ly:music? elt) (loop elt last-chord) last-chord)
639                 (ly:music-property music 'elements)))))
640   music)
641
642 ;;; splitting chords into voices.
643 (define (voicify-list lst number)
644   "Make a list of Musics.
645
646 voicify-list :: [ [Music ] ] -> number -> [Music]
647 LST is a list music-lists.
648
649 NUMBER is 0-base, i.e., Voice=1 (upstems) has number 0.
650 "
651   (if (null? lst)
652       '()
653       (cons (context-spec-music
654              (make-sequential-music
655               (list (make-voice-props-set number)
656                     (make-simultaneous-music (car lst))))
657              'Bottom  (number->string (1+ number)))
658             (voicify-list (cdr lst) (1+ number)))))
659
660 (define (voicify-chord ch)
661   "Split the parts of a chord into different Voices using separator"
662   (let ((es (ly:music-property ch 'elements)))
663     (set! (ly:music-property  ch 'elements)
664           (voicify-list (split-list-by-separator es music-separator?) 0))
665     ch))
666
667 (define-public (voicify-music m)
668   "Recursively split chords that are separated with @code{\\\\}."
669   (if (not (ly:music? m))
670       (ly:error (_ "music expected: ~S") m))
671   (let ((es (ly:music-property m 'elements))
672         (e (ly:music-property m 'element)))
673
674     (if (pair? es)
675         (set! (ly:music-property m 'elements) (map voicify-music es)))
676     (if (ly:music? e)
677         (set! (ly:music-property m 'element)  (voicify-music e)))
678     (if (and (equal? (ly:music-property m 'name) 'SimultaneousMusic)
679              (reduce (lambda (x y ) (or x y)) #f (map music-separator? es)))
680         (set! m (context-spec-music (voicify-chord m) 'Staff)))
681     m))
682
683 (define-public (empty-music)
684   (make-music 'Music))
685
686 ;; Make a function that checks score element for being of a specific type.
687 (define-public (make-type-checker symbol)
688   (lambda (elt)
689     (grob::has-interface elt symbol)))
690
691 (define-public ((outputproperty-compatibility func sym val) grob g-context ao-context)
692   (if (func grob)
693       (set! (ly:grob-property grob sym) val)))
694
695
696 (define-public ((set-output-property grob-name symbol val)  grob grob-c context)
697   "Usage example:
698 @code{\\applyoutput #(set-output-property 'Clef 'extra-offset '(0 . 1))}"
699   (let ((meta (ly:grob-property grob 'meta)))
700     (if (equal? (assoc-get 'name meta) grob-name)
701         (set! (ly:grob-property grob symbol) val))))
702
703
704 (define-public (skip->rest mus)
705   "Replace @var{mus} by @code{RestEvent} of the same duration if it is a
706 @code{SkipEvent}.  Useful for extracting parts from crowded scores."
707
708   (if  (memq (ly:music-property mus 'name) '(SkipEvent SkipMusic))
709    (make-music 'RestEvent 'duration (ly:music-property mus 'duration))
710    mus))
711
712
713 (define-public (music-has-type music type)
714   (memq type (ly:music-property music 'types)))
715
716 (define-public (music-clone music)
717   (define (alist->args alist acc)
718     (if (null? alist)
719         acc
720         (alist->args (cdr alist)
721                      (cons (caar alist) (cons (cdar alist) acc)))))
722
723   (apply
724    make-music
725    (ly:music-property music 'name)
726    (alist->args (ly:music-mutable-properties music) '())))
727
728 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
729 ;; warn for bare chords at start.
730
731 (define-public (ly:music-message music msg)
732   (let ((ip (ly:music-property music 'origin)))
733     (if (ly:input-location? ip)
734         (ly:input-message ip msg)
735         (ly:message msg))))
736
737 (define-public (ly:music-warning music msg)
738   (let ((ip (ly:music-property music 'origin)))
739     (if (ly:input-location? ip)
740         (ly:input-warning ip msg)
741         (ly:warning msg))))
742
743 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
744 ;;
745 ;; setting stuff for grace context.
746 ;;
747
748 (define (vector-extend v x)
749   "Make a new vector consisting of V, with X added to the end."
750   (let* ((n (vector-length v))
751          (nv (make-vector (+ n 1) '())))
752     (vector-move-left! v 0 n nv 0)
753     (vector-set! nv n x)
754     nv))
755
756 (define (vector-map f v)
757   "Map F over V.  This function returns nothing."
758   (do ((n (vector-length v))
759        (i 0 (+ i 1)))
760       ((>= i n))
761     (f (vector-ref v i))))
762
763 (define (vector-reverse-map f v)
764   "Map F over V, N to 0 order.  This function returns nothing."
765   (do ((i (- (vector-length v) 1) (- i 1)))
766       ((< i 0))
767     (f (vector-ref v i))))
768
769 (define-public (add-grace-property context-name grob sym val)
770   "Set @var{sym}=@var{val} for @var{grob} in @var{context-name}."
771   (define (set-prop context)
772     (let* ((where (ly:context-property-where-defined context 'graceSettings))
773            (current (ly:context-property where 'graceSettings))
774            (new-settings (append current
775                                  (list (list context-name grob sym val)))))
776       (ly:context-set-property! where 'graceSettings new-settings)))
777   (context-spec-music (make-apply-context set-prop) 'Voice))
778
779 (define-public (remove-grace-property context-name grob sym)
780   "Remove all @var{sym} for @var{grob} in @var{context-name}."
781   (define (sym-grob-context? property sym grob context-name)
782     (and (eq? (car property) context-name)
783          (eq? (cadr property) grob)
784          (eq? (caddr property) sym)))
785   (define (delete-prop context)
786     (let* ((where (ly:context-property-where-defined context 'graceSettings))
787            (current (ly:context-property where 'graceSettings))
788            (prop-settings (filter
789                             (lambda(x) (sym-grob-context? x sym grob context-name))
790                             current))
791            (new-settings current))
792       (for-each (lambda(x)
793                  (set! new-settings (delete x new-settings)))
794                prop-settings)
795       (ly:context-set-property! where 'graceSettings new-settings)))
796   (context-spec-music (make-apply-context delete-prop) 'Voice))
797
798
799
800 (defmacro-public def-grace-function (start stop . docstring)
801   "Helper macro for defining grace music"
802   `(define-music-function (parser location music) (ly:music?)
803      ,@docstring
804      (make-music 'GraceMusic
805                  'origin location
806                  'element (make-music 'SequentialMusic
807                                       'elements (list (ly:music-deep-copy ,start)
808                                                       music
809                                                       (ly:music-deep-copy ,stop))))))
810
811 (defmacro-public define-syntax-function (type args signature . body)
812   "Helper macro for `ly:make-music-function'.
813 Syntax:
814   (define-syntax-function (result-type? parser location arg1 arg2 ...) (result-type? arg1-type arg2-type ...)
815     ...function body...)
816
817 argX-type can take one of the forms @code{predicate?} for mandatory
818 arguments satisfying the predicate, @code{(predicate?)} for optional
819 parameters of that type defaulting to @code{#f}, @code{@w{(predicate?
820 value)}} for optional parameters with a specified default
821 value (evaluated at definition time).  An optional parameter can be
822 omitted in a call only when it can't get confused with a following
823 parameter of different type.
824
825 Predicates with syntactical significance are @code{ly:pitch?},
826 @code{ly:duration?}, @code{ly:music?}, @code{markup?}.  Other
827 predicates require the parameter to be entered as Scheme expression.
828
829 @code{result-type?} can specify a default in the same manner as
830 predicates, to be used in case of a type error in arguments or
831 result."
832
833   (set! signature (map (lambda (pred)
834                          (if (pair? pred)
835                              `(cons ,(car pred)
836                                     ,(and (pair? (cdr pred)) (cadr pred)))
837                              pred))
838                        (cons type signature)))
839   (if (and (pair? body) (pair? (car body)) (eqv? '_i (caar body)))
840       ;; When the music function definition contains a i10n doc string,
841       ;; (_i "doc string"), keep the literal string only
842       (let ((docstring (cadar body))
843             (body (cdr body)))
844         `(ly:make-music-function (list ,@signature)
845                                  (lambda ,args
846                                    ,docstring
847                                    ,@body)))
848       `(ly:make-music-function (list ,@signature)
849                                (lambda ,args
850                                  ,@body))))
851
852 (defmacro-public define-music-function rest
853   "Defining macro returning music functions.
854 Syntax:
855   (define-music-function (parser location arg1 arg2 ...) (arg1-type? arg2-type? ...)
856     ...function body...)
857
858 argX-type can take one of the forms @code{predicate?} for mandatory
859 arguments satisfying the predicate, @code{(predicate?)} for optional
860 parameters of that type defaulting to @code{#f}, @code{@w{(predicate?
861 value)}} for optional parameters with a specified default
862 value (evaluated at definition time).  An optional parameter can be
863 omitted in a call only when it can't get confused with a following
864 parameter of different type.
865
866 Predicates with syntactical significance are @code{ly:pitch?},
867 @code{ly:duration?}, @code{ly:music?}, @code{markup?}.  Other
868 predicates require the parameter to be entered as Scheme expression.
869
870 Must return a music expression.  The @code{origin} is automatically
871 set to the @code{location} parameter."
872
873   `(define-syntax-function (ly:music? (make-music 'Music 'void #t)) ,@rest))
874
875
876 (defmacro-public define-scheme-function rest
877   "Defining macro returning Scheme functions.
878 Syntax:
879   (define-scheme-function (parser location arg1 arg2 ...) (arg1-type? arg2-type? ...)
880     ...function body...)
881
882 argX-type can take one of the forms @code{predicate?} for mandatory
883 arguments satisfying the predicate, @code{(predicate?)} for optional
884 parameters of that type defaulting to @code{#f}, @code{@w{(predicate?
885 value)}} for optional parameters with a specified default
886 value (evaluated at definition time).  An optional parameter can be
887 omitted in a call only when it can't get confused with a following
888 parameter of different type.
889
890 Predicates with syntactical significance are @code{ly:pitch?},
891 @code{ly:duration?}, @code{ly:music?}, @code{markup?}.  Other
892 predicates require the parameter to be entered as Scheme expression.
893
894 Can return arbitrary expressions.  If a music expression is returned,
895 its @code{origin} is automatically set to the @code{location}
896 parameter."
897
898   `(define-syntax-function scheme? ,@rest))
899
900 (defmacro-public define-void-function rest
901   "This defines a Scheme function like @code{define-scheme-function} with
902 void return value (i.e., what most Guile functions with `unspecified'
903 value return).  Use this when defining functions for executing actions
904 rather than returning values, to keep Lilypond from trying to interpret
905 the return value."
906   `(define-syntax-function (void? *unspecified*) ,@rest *unspecified*))
907
908 (defmacro-public define-event-function rest
909   "Defining macro returning event functions.
910 Syntax:
911   (define-event-function (parser location arg1 arg2 ...) (arg1-type? arg2-type? ...)
912     ...function body...)
913
914 argX-type can take one of the forms @code{predicate?} for mandatory
915 arguments satisfying the predicate, @code{(predicate?)} for optional
916 parameters of that type defaulting to @code{#f}, @code{@w{(predicate?
917 value)}} for optional parameters with a specified default
918 value (evaluated at definition time).  An optional parameter can be
919 omitted in a call only when it can't get confused with a following
920 parameter of different type.
921
922 Predicates with syntactical significance are @code{ly:pitch?},
923 @code{ly:duration?}, @code{ly:music?}, @code{markup?}.  Other
924 predicates require the parameter to be entered as Scheme expression.
925
926 Must return an event expression.  The @code{origin} is automatically
927 set to the @code{location} parameter."
928
929   `(define-syntax-function (ly:event? (make-music 'Event 'void #t)) ,@rest))
930
931 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
932
933 (define-public (cue-substitute quote-music)
934   "Must happen after @code{quote-substitute}."
935
936   (if (vector? (ly:music-property quote-music 'quoted-events))
937       (let* ((dir (ly:music-property quote-music 'quoted-voice-direction))
938              (clef (ly:music-property quote-music 'quoted-music-clef))
939              (main-voice (if (eq? 1 dir) 1 0))
940              (cue-voice (if (eq? 1 dir) 0 1))
941              (main-music (ly:music-property quote-music 'element))
942              (return-value quote-music))
943
944         (if (or (eq? 1 dir) (eq? -1 dir))
945
946             ;; if we have stem dirs, change both quoted and main music
947             ;; to have opposite stems.
948             (begin
949               (set! return-value
950                     ;; cannot context-spec Quote-music, since context
951                     ;; for the quotes is determined in the iterator.
952                     (make-sequential-music
953                      (list
954                       (if (null? clef)
955                           (make-music 'Music)
956                           (make-cue-clef-set clef))
957                       (context-spec-music (make-voice-props-set cue-voice) 'CueVoice "cue")
958                       quote-music
959                       (context-spec-music (make-voice-props-revert) 'CueVoice "cue")
960                       (if (null? clef)
961                           (make-music 'Music)
962                           (make-cue-clef-unset)))))
963               (set! main-music
964                     (make-sequential-music
965                      (list
966                       (make-voice-props-set main-voice)
967                       main-music
968                       (make-voice-props-revert))))
969               (set! (ly:music-property quote-music 'element) main-music)))
970
971         return-value)
972       quote-music))
973
974 (define-public ((quote-substitute quote-tab) music)
975   (let* ((quoted-name (ly:music-property music 'quoted-music-name))
976          (quoted-vector (and (string? quoted-name)
977                              (hash-ref quote-tab quoted-name #f))))
978
979
980     (if (string? quoted-name)
981         (if (vector? quoted-vector)
982             (begin
983               (set! (ly:music-property music 'quoted-events) quoted-vector)
984               (set! (ly:music-property music 'iterator-ctor)
985                     ly:quote-iterator::constructor))
986             (ly:music-warning music (ly:format (_ "cannot find quoted music: `~S'") quoted-name))))
987     music))
988
989
990 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
991 ;; switch it on here, so parsing and init isn't checked (too slow!)
992 ;;
993 ;; automatic music transformations.
994
995 (define (switch-on-debugging m)
996   (if (defined? 'set-debug-cell-accesses!)
997       (set-debug-cell-accesses! 15000))
998   m)
999
1000 (define (music-check-error music)
1001   (define found #f)
1002   (define (signal m)
1003     (if (and (ly:music? m)
1004              (eq? (ly:music-property m 'error-found) #t))
1005         (set! found #t)))
1006
1007   (for-each signal (ly:music-property music 'elements))
1008   (signal (ly:music-property music 'element))
1009
1010   (if found
1011       (set! (ly:music-property music 'error-found) #t))
1012   music)
1013
1014 (define (precompute-music-length music)
1015   (set! (ly:music-property music 'length)
1016         (ly:music-length music))
1017   music)
1018
1019 (define-public (make-duration-of-length moment)
1020  "Make duration of the given @code{moment} length."
1021  (ly:make-duration 0 0
1022   (ly:moment-main-numerator moment)
1023   (ly:moment-main-denominator moment)))
1024
1025 (define (make-skipped moment bool)
1026  "Depending on BOOL, set or unset skipTypesetting,
1027 then make SkipMusic of the given MOMENT length, and
1028 then revert skipTypesetting."
1029  (make-sequential-music
1030   (list
1031    (context-spec-music (make-property-set 'skipTypesetting bool)
1032     'Score)
1033    (make-music 'SkipMusic 'duration
1034     (make-duration-of-length moment))
1035    (context-spec-music (make-property-set 'skipTypesetting (not bool))
1036     'Score))))
1037
1038 (define (skip-as-needed music parser)
1039   "Replace MUSIC by
1040  << {  \\set skipTypesetting = ##f
1041  LENGTHOF(\\showFirstLength)
1042  \\set skipTypesetting = ##t
1043  LENGTHOF(\\showLastLength) }
1044  MUSIC >>
1045  if appropriate.
1046
1047  When only showFirstLength is set,
1048  the 'length property of the music is
1049  overridden to speed up compiling."
1050   (let*
1051       ((show-last (ly:parser-lookup parser 'showLastLength))
1052        (show-first (ly:parser-lookup parser 'showFirstLength))
1053        (show-last-length (and (ly:music? show-last)
1054                               (ly:music-length show-last)))
1055        (show-first-length (and (ly:music? show-first)
1056                                (ly:music-length show-first)))
1057        (orig-length (ly:music-length music)))
1058
1059     ;;FIXME: if using either showFirst- or showLastLength,
1060     ;; make sure that skipBars is not set.
1061
1062     (cond
1063
1064      ;; both properties may be set.
1065      ((and show-first-length show-last-length)
1066       (let
1067           ((skip-length (ly:moment-sub orig-length show-last-length)))
1068         (make-simultaneous-music
1069          (list
1070           (make-sequential-music
1071            (list
1072             (make-skipped skip-length #t)
1073             ;; let's draw a separator between the beginning and the end
1074             (context-spec-music (make-property-set 'whichBar "||")
1075                                 'Timing)))
1076           (make-skipped show-first-length #f)
1077           music))))
1078
1079      ;; we may only want to print the last length
1080      (show-last-length
1081       (let
1082           ((skip-length (ly:moment-sub orig-length show-last-length)))
1083         (make-simultaneous-music
1084          (list
1085           (make-skipped skip-length #t)
1086           music))))
1087
1088      ;; we may only want to print the beginning; in this case
1089      ;; only the first length will be processed (much faster).
1090      (show-first-length
1091       ;; the first length must not exceed the original length.
1092       (if (ly:moment<? show-first-length orig-length)
1093           (set! (ly:music-property music 'length)
1094                 show-first-length))
1095       music)
1096
1097      (else music))))
1098
1099
1100 (define-public toplevel-music-functions
1101   (list
1102    (lambda (music parser) (expand-repeat-chords!
1103                            (cons 'rhythmic-event
1104                                  (ly:parser-lookup parser '$chord-repeat-events))
1105                            music))
1106    (lambda (music parser) (voicify-music music))
1107    (lambda (x parser) (music-map music-check-error x))
1108    (lambda (x parser) (music-map precompute-music-length x))
1109    (lambda (music parser)
1110
1111      (music-map (quote-substitute (ly:parser-lookup parser 'musicQuotes))  music))
1112
1113    ;; switch-on-debugging
1114    (lambda (x parser) (music-map cue-substitute x))
1115
1116    (lambda (x parser)
1117      (skip-as-needed x parser)
1118    )))
1119
1120 ;;;;;;;;;;
1121 ;;; general purpose music functions
1122
1123 (define (shift-octave pitch octave-shift)
1124   (_i "Add @var{octave-shift} to the octave of @var{pitch}.")
1125   (ly:make-pitch
1126      (+ (ly:pitch-octave pitch) octave-shift)
1127      (ly:pitch-notename pitch)
1128      (ly:pitch-alteration pitch)))
1129
1130
1131 ;;;;;;;;;;;;;;;;;
1132 ;; lyrics
1133
1134 (define (apply-durations lyric-music durations)
1135   (define (apply-duration music)
1136     (if (and (not (equal? (ly:music-length music) ZERO-MOMENT))
1137              (ly:duration?  (ly:music-property music 'duration)))
1138         (begin
1139           (set! (ly:music-property music 'duration) (car durations))
1140           (set! durations (cdr durations)))))
1141
1142   (music-map apply-duration lyric-music))
1143
1144
1145 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1146 ;; accidentals
1147
1148 (define (recent-enough? bar-number alteration-def laziness)
1149   (or (number? alteration-def)
1150       (equal? laziness #t)
1151       (<= bar-number (+ (cadr alteration-def) laziness))))
1152
1153 (define (accidental-invalid? alteration-def)
1154   "Checks an alteration entry for being invalid.
1155
1156 Non-key alterations are invalidated when tying into the next bar or
1157 when there is a clef change, since neither repetition nor cancellation
1158 can be omitted when the same note occurs again.
1159
1160 Returns @code{#f} or the reason for the invalidation, a symbol."
1161   (let* ((def (if (pair? alteration-def)
1162                   (car alteration-def)
1163                   alteration-def)))
1164     (and (symbol? def) def)))
1165
1166 (define (extract-alteration alteration-def)
1167   (cond ((number? alteration-def)
1168          alteration-def)
1169         ((pair? alteration-def)
1170          (car alteration-def))
1171         (else 0)))
1172
1173 (define (check-pitch-against-signature context pitch barnum laziness octaveness)
1174   "Checks the need for an accidental and a @q{restore} accidental against
1175 @code{localKeySignature}.  The @var{laziness} is the number of measures
1176 for which reminder accidentals are used (i.e., if @var{laziness} is zero,
1177 only cancel accidentals in the same measure; if @var{laziness} is three,
1178 we cancel accidentals up to three measures after they first appear.
1179 @var{octaveness} is either @code{'same-octave} or @code{'any-octave} and
1180 specifies whether accidentals should be canceled in different octaves."
1181   (let* ((ignore-octave (cond ((equal? octaveness 'any-octave) #t)
1182                               ((equal? octaveness 'same-octave) #f)
1183                               (else
1184                                (ly:warning (_ "Unknown octaveness type: ~S ") octaveness)
1185                                (ly:warning (_ "Defaulting to 'any-octave."))
1186                                #t)))
1187          (key-sig (ly:context-property context 'keySignature))
1188          (local-key-sig (ly:context-property context 'localKeySignature))
1189          (notename (ly:pitch-notename pitch))
1190          (octave (ly:pitch-octave pitch))
1191          (pitch-handle (cons octave notename))
1192          (need-restore #f)
1193          (need-accidental #f)
1194          (previous-alteration #f)
1195          (from-other-octaves #f)
1196          (from-same-octave (assoc-get pitch-handle local-key-sig))
1197          (from-key-sig (or (assoc-get notename local-key-sig)
1198
1199     ;; If no key signature match is found from localKeySignature, we may have a custom
1200     ;; type with octave-specific entries of the form ((octave . pitch) alteration)
1201     ;; instead of (pitch . alteration).  Since this type cannot coexist with entries in
1202     ;; localKeySignature, try extracting from keySignature instead.
1203                            (assoc-get pitch-handle key-sig))))
1204
1205     ;; loop through localKeySignature to search for a notename match from other octaves
1206     (let loop ((l local-key-sig))
1207       (if (pair? l)
1208           (let ((entry (car l)))
1209             (if (and (pair? (car entry))
1210                      (= (cdar entry) notename))
1211                 (set! from-other-octaves (cdr entry))
1212                 (loop (cdr l))))))
1213
1214     ;; find previous alteration-def for comparison with pitch
1215     (cond
1216      ;; from same octave?
1217      ((and (not ignore-octave)
1218            from-same-octave
1219            (recent-enough? barnum from-same-octave laziness))
1220       (set! previous-alteration from-same-octave))
1221
1222      ;; from any octave?
1223      ((and ignore-octave
1224            from-other-octaves
1225            (recent-enough? barnum from-other-octaves laziness))
1226       (set! previous-alteration from-other-octaves))
1227
1228      ;; not recent enough, extract from key signature/local key signature
1229      (from-key-sig
1230       (set! previous-alteration from-key-sig)))
1231
1232     (if (accidental-invalid? previous-alteration)
1233         (set! need-accidental #t)
1234
1235         (let* ((prev-alt (extract-alteration previous-alteration))
1236                (this-alt (ly:pitch-alteration pitch)))
1237
1238           (if (not (= this-alt prev-alt))
1239               (begin
1240                 (set! need-accidental #t)
1241                 (if (and (not (= this-alt 0))
1242                          (and (< (abs this-alt) (abs prev-alt))
1243                              (> (* prev-alt this-alt) 0)))
1244                     (set! need-restore #t))))))
1245
1246     (cons need-restore need-accidental)))
1247
1248 (define-public ((make-accidental-rule octaveness laziness) context pitch barnum measurepos)
1249   "Create an accidental rule that makes its decision based on the octave of
1250 the note and a laziness value.
1251
1252 @var{octaveness} is either @code{'same-octave} or @code{'any-octave} and
1253 defines whether the rule should respond to accidental changes in other
1254 octaves than the current.  @code{'same-octave} is the normal way to typeset
1255 accidentals -- an accidental is made if the alteration is different from the
1256 last active pitch in the same octave.  @code{'any-octave} looks at the last
1257 active pitch in any octave.
1258
1259 @var{laziness} states over how many bars an accidental should be remembered.
1260 @code{0}@tie{}is the default -- accidental lasts over 0@tie{}bar lines, that
1261 is, to the end of current measure.  A positive integer means that the
1262 accidental lasts over that many bar lines.  @w{@code{-1}} is `forget
1263 immediately', that is, only look at key signature.  @code{#t} is `forever'."
1264
1265   (check-pitch-against-signature context pitch barnum laziness octaveness))
1266
1267 (define (key-entry-notename entry)
1268   "Return the pitch of an entry in localKeySignature.  The entry is either of the form
1269   '(notename . alter) or '((octave . notename) . (alter barnum . measurepos))."
1270   (if (number? (car entry))
1271       (car entry)
1272       (cdar entry)))
1273
1274 (define (key-entry-octave entry)
1275   "Return the octave of an entry in localKeySignature (or #f if the entry does not have
1276   an octave)."
1277   (and (pair? (car entry)) (caar entry)))
1278
1279 (define (key-entry-bar-number entry)
1280   "Return the bar number of an entry in localKeySignature (or #f if the entry does not
1281   have a bar number)."
1282   (and (pair? (car entry)) (caddr entry)))
1283
1284 (define (key-entry-measure-position entry)
1285   "Return the measure position of an entry in localKeySignature (or #f if the entry does
1286   not have a measure position)."
1287   (and (pair? (car entry)) (cdddr entry)))
1288
1289 (define (key-entry-alteration entry)
1290   "Return the alteration of an entry in localKeySignature.
1291
1292 For convenience, returns @code{0} if entry is @code{#f}."
1293   (if entry
1294       (if (number? (car entry))
1295           (cdr entry)
1296           (cadr entry))
1297       0))
1298
1299 (define-public (find-pitch-entry keysig pitch accept-global accept-local)
1300   "Return the first entry in @var{keysig} that matches @var{pitch}.
1301 @var{accept-global} states whether key signature entries should be included.
1302 @var{accept-local} states whether local accidentals should be included.
1303 If no matching entry is found, @var{#f} is returned."
1304   (and (pair? keysig)
1305        (let* ((entry (car keysig))
1306               (entryoct (key-entry-octave entry))
1307               (entrynn (key-entry-notename entry))
1308               (oct (ly:pitch-octave pitch))
1309               (nn (ly:pitch-notename pitch)))
1310          (if (and (equal? nn entrynn)
1311                   (or (and accept-global (not entryoct))
1312                       (and accept-local (equal? oct entryoct))))
1313              entry
1314              (find-pitch-entry (cdr keysig) pitch accept-global accept-local)))))
1315
1316 (define-public (neo-modern-accidental-rule context pitch barnum measurepos)
1317   "An accidental rule that typesets an accidental if it differs from the
1318 key signature @emph{and} does not directly follow a note on the same
1319 staff line.  This rule should not be used alone because it does neither
1320 look at bar lines nor different accidentals at the same note name."
1321   (let* ((keysig (ly:context-property context 'localKeySignature))
1322          (entry (find-pitch-entry keysig pitch #t #t)))
1323     (if (not entry)
1324         (cons #f #f)
1325         (let* ((global-entry (find-pitch-entry keysig pitch #t #f))
1326                (key-acc (key-entry-alteration global-entry))
1327                (acc (ly:pitch-alteration pitch))
1328                (entrymp (key-entry-measure-position entry))
1329                (entrybn (key-entry-bar-number entry)))
1330           (cons #f (not (or (equal? acc key-acc)
1331                             (and (equal? entrybn barnum) (equal? entrymp measurepos)))))))))
1332
1333 (define-public (teaching-accidental-rule context pitch barnum measurepos)
1334   "An accidental rule that typesets a cautionary accidental if it is
1335 included in the key signature @emph{and} does not directly follow a note
1336 on the same staff line."
1337   (let* ((keysig (ly:context-property context 'localKeySignature))
1338          (entry (find-pitch-entry keysig pitch #t #t)))
1339     (if (not entry)
1340         (cons #f #f)
1341         (let* ((global-entry (find-pitch-entry keysig pitch #f #f))
1342                (key-acc (key-entry-alteration global-entry))
1343                (acc (ly:pitch-alteration pitch))
1344                (entrymp (key-entry-measure-position entry))
1345                (entrybn (key-entry-bar-number entry)))
1346           (cons #f (not (or (equal? acc key-acc)
1347                             (and (equal? entrybn barnum) (equal? entrymp measurepos)))))))))
1348
1349 (define-public (set-accidentals-properties extra-natural
1350                                            auto-accs auto-cauts
1351                                            context)
1352   (context-spec-music
1353    (make-sequential-music
1354     (append (if (boolean? extra-natural)
1355                 (list (make-property-set 'extraNatural extra-natural))
1356                 '())
1357             (list (make-property-set 'autoAccidentals auto-accs)
1358                   (make-property-set 'autoCautionaries auto-cauts))))
1359    context))
1360
1361 (define-public (set-accidental-style style . rest)
1362   "Set accidental style to @var{style}.  Optionally take a context
1363 argument, e.g. @code{'Staff} or @code{'Voice}.  The context defaults
1364 to @code{Staff}, except for piano styles, which use @code{GrandStaff}
1365 as a context."
1366   (let ((context (if (pair? rest)
1367                      (car rest) 'Staff))
1368         (pcontext (if (pair? rest)
1369                       (car rest) 'GrandStaff)))
1370     (cond
1371       ;; accidentals as they were common in the 18th century.
1372       ((equal? style 'default)
1373        (set-accidentals-properties #t
1374                                    `(Staff ,(make-accidental-rule 'same-octave 0))
1375                                    '()
1376                                    context))
1377       ;; accidentals from one voice do NOT get canceled in other voices
1378       ((equal? style 'voice)
1379        (set-accidentals-properties #t
1380                                    `(Voice ,(make-accidental-rule 'same-octave 0))
1381                                    '()
1382                                    context))
1383       ;; accidentals as suggested by Kurt Stone, Music Notation in the 20th century.
1384       ;; This includes all the default accidentals, but accidentals also needs canceling
1385       ;; in other octaves and in the next measure.
1386       ((equal? style 'modern)
1387        (set-accidentals-properties #f
1388                                    `(Staff ,(make-accidental-rule 'same-octave 0)
1389                                            ,(make-accidental-rule 'any-octave 0)
1390                                            ,(make-accidental-rule 'same-octave 1))
1391                                    '()
1392                                    context))
1393       ;; the accidentals that Stone adds to the old standard as cautionaries
1394       ((equal? style 'modern-cautionary)
1395        (set-accidentals-properties #f
1396                                    `(Staff ,(make-accidental-rule 'same-octave 0))
1397                                    `(Staff ,(make-accidental-rule 'any-octave 0)
1398                                            ,(make-accidental-rule 'same-octave 1))
1399                                    context))
1400       ;; same as modern, but accidentals different from the key signature are always
1401       ;; typeset - unless they directly follow a note of the same pitch.
1402       ((equal? style 'neo-modern)
1403        (set-accidentals-properties #f
1404                                    `(Staff ,(make-accidental-rule 'same-octave 0)
1405                                            ,(make-accidental-rule 'any-octave 0)
1406                                            ,(make-accidental-rule 'same-octave 1)
1407                                            ,neo-modern-accidental-rule)
1408                                    '()
1409                                    context))
1410       ((equal? style 'neo-modern-cautionary)
1411        (set-accidentals-properties #f
1412                                    `(Staff ,(make-accidental-rule 'same-octave 0))
1413                                    `(Staff ,(make-accidental-rule 'any-octave 0)
1414                                            ,(make-accidental-rule 'same-octave 1)
1415                                            ,neo-modern-accidental-rule)
1416                                    context))
1417       ((equal? style 'neo-modern-voice)
1418        (set-accidentals-properties #f
1419                                    `(Voice ,(make-accidental-rule 'same-octave 0)
1420                                            ,(make-accidental-rule 'any-octave 0)
1421                                            ,(make-accidental-rule 'same-octave 1)
1422                                            ,neo-modern-accidental-rule
1423                                      Staff ,(make-accidental-rule 'same-octave 0)
1424                                            ,(make-accidental-rule 'any-octave 0)
1425                                            ,(make-accidental-rule 'same-octave 1)
1426                                       ,neo-modern-accidental-rule)
1427                                    '()
1428                                    context))
1429       ((equal? style 'neo-modern-voice-cautionary)
1430        (set-accidentals-properties #f
1431                                    `(Voice ,(make-accidental-rule 'same-octave 0))
1432                                    `(Voice ,(make-accidental-rule 'any-octave 0)
1433                                            ,(make-accidental-rule 'same-octave 1)
1434                                            ,neo-modern-accidental-rule
1435                                      Staff ,(make-accidental-rule 'same-octave 0)
1436                                            ,(make-accidental-rule 'any-octave 0)
1437                                            ,(make-accidental-rule 'same-octave 1)
1438                                            ,neo-modern-accidental-rule)
1439                                    context))
1440       ;; Accidentals as they were common in dodecaphonic music with no tonality.
1441       ;; Each note gets one accidental.
1442       ((equal? style 'dodecaphonic)
1443        (set-accidentals-properties #f
1444                                    `(Staff ,(lambda (c p bn mp) '(#f . #t)))
1445                                    '()
1446                                    context))
1447       ;; Multivoice accidentals to be read both by musicians playing one voice
1448       ;; and musicians playing all voices.
1449       ;; Accidentals are typeset for each voice, but they ARE canceled across voices.
1450       ((equal? style 'modern-voice)
1451        (set-accidentals-properties  #f
1452                                     `(Voice ,(make-accidental-rule 'same-octave 0)
1453                                             ,(make-accidental-rule 'any-octave 0)
1454                                             ,(make-accidental-rule 'same-octave 1)
1455                                       Staff ,(make-accidental-rule 'same-octave 0)
1456                                             ,(make-accidental-rule 'any-octave 0)
1457                                             ,(make-accidental-rule 'same-octave 1))
1458                                     '()
1459                                     context))
1460       ;; same as modernVoiceAccidental eccept that all special accidentals are typeset
1461       ;; as cautionaries
1462       ((equal? style 'modern-voice-cautionary)
1463        (set-accidentals-properties #f
1464                                    `(Voice ,(make-accidental-rule 'same-octave 0))
1465                                    `(Voice ,(make-accidental-rule 'any-octave 0)
1466                                            ,(make-accidental-rule 'same-octave 1)
1467                                      Staff ,(make-accidental-rule 'same-octave 0)
1468                                            ,(make-accidental-rule 'any-octave 0)
1469                                            ,(make-accidental-rule 'same-octave 1))
1470                                    context))
1471       ;; stone's suggestions for accidentals on grand staff.
1472       ;; Accidentals are canceled across the staves in the same grand staff as well
1473       ((equal? style 'piano)
1474        (set-accidentals-properties #f
1475                                    `(Staff ,(make-accidental-rule 'same-octave 0)
1476                                            ,(make-accidental-rule 'any-octave 0)
1477                                            ,(make-accidental-rule 'same-octave 1)
1478                                      GrandStaff
1479                                            ,(make-accidental-rule 'any-octave 0)
1480                                            ,(make-accidental-rule 'same-octave 1))
1481                                    '()
1482                                    pcontext))
1483       ((equal? style 'piano-cautionary)
1484        (set-accidentals-properties #f
1485                                    `(Staff ,(make-accidental-rule 'same-octave 0))
1486                                    `(Staff ,(make-accidental-rule 'any-octave 0)
1487                                            ,(make-accidental-rule 'same-octave 1)
1488                                      GrandStaff
1489                                            ,(make-accidental-rule 'any-octave 0)
1490                                            ,(make-accidental-rule 'same-octave 1))
1491                                    pcontext))
1492
1493       ;; same as modern, but cautionary accidentals are printed for all sharp or flat
1494       ;; tones specified by the key signature.
1495        ((equal? style 'teaching)
1496        (set-accidentals-properties #f
1497                                     `(Staff ,(make-accidental-rule 'same-octave 0))
1498                                     `(Staff ,(make-accidental-rule 'same-octave 1)
1499                                            ,teaching-accidental-rule)
1500                                    context))
1501
1502       ;; do not set localKeySignature when a note alterated differently from
1503       ;; localKeySignature is found.
1504       ;; Causes accidentals to be printed at every note instead of
1505       ;; remembered for the duration of a measure.
1506       ;; accidentals not being remembered, causing accidentals always to
1507       ;; be typeset relative to the time signature
1508       ((equal? style 'forget)
1509        (set-accidentals-properties '()
1510                                    `(Staff ,(make-accidental-rule 'same-octave -1))
1511                                    '()
1512                                    context))
1513       ;; Do not reset the key at the start of a measure.  Accidentals will be
1514       ;; printed only once and are in effect until overridden, possibly many
1515       ;; measures later.
1516       ((equal? style 'no-reset)
1517        (set-accidentals-properties '()
1518                                    `(Staff ,(make-accidental-rule 'same-octave #t))
1519                                    '()
1520                                    context))
1521       (else
1522        (ly:warning (_ "unknown accidental style: ~S") style)
1523        (make-sequential-music '())))))
1524
1525 (define-public (invalidate-alterations context)
1526   "Invalidate alterations in @var{context}.
1527
1528 Elements of @code{'localKeySignature} corresponding to local
1529 alterations of the key signature have the form
1530 @code{'((octave . notename) . (alter barnum . measurepos))}.
1531 Replace them with a version where @code{alter} is set to @code{'clef}
1532 to force a repetition of accidentals.
1533
1534 Entries that conform with the current key signature are not invalidated."
1535   (let* ((keysig (ly:context-property context 'keySignature)))
1536     (set! (ly:context-property context 'localKeySignature)
1537           (map-in-order
1538            (lambda (entry)
1539              (let* ((localalt (key-entry-alteration entry))
1540                     (localoct (key-entry-octave entry)))
1541                (if (or (accidental-invalid? localalt)
1542                        (not localoct)
1543                        (= localalt
1544                           (key-entry-alteration
1545                            (find-pitch-entry
1546                             keysig
1547                             (ly:make-pitch localoct
1548                                            (key-entry-notename entry)
1549                                            0)
1550                             #t #t))))
1551                    entry
1552                    (cons (car entry) (cons 'clef (cddr entry))))))
1553            (ly:context-property context 'localKeySignature)))))
1554
1555 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1556
1557 (define-public (skip-of-length mus)
1558   "Create a skip of exactly the same length as @var{mus}."
1559   (let* ((skip
1560           (make-music
1561            'SkipEvent
1562            'duration (ly:make-duration 0 0))))
1563
1564     (make-event-chord (list (ly:music-compress skip (ly:music-length mus))))))
1565
1566 (define-public (mmrest-of-length mus)
1567   "Create a multi-measure rest of exactly the same length as @var{mus}."
1568
1569   (let* ((skip
1570           (make-multi-measure-rest
1571            (ly:make-duration 0 0) '())))
1572     (ly:music-compress skip (ly:music-length mus))
1573     skip))
1574
1575 (define-public (pitch-of-note event-chord)
1576   (let ((evs (filter (lambda (x)
1577                        (music-has-type x 'note-event))
1578                      (ly:music-property event-chord 'elements))))
1579
1580     (and (pair? evs)
1581          (ly:music-property (car evs) 'pitch))))
1582
1583 (define-public (duration-of-note event-chord)
1584   (cond
1585    ((pair? event-chord)
1586     (or (duration-of-note (car event-chord))
1587         (duration-of-note (cdr event-chord))))
1588    ((ly:music? event-chord)
1589     (let ((dur (ly:music-property event-chord 'duration)))
1590       (if (ly:duration? dur)
1591           dur
1592           (duration-of-note (ly:music-property event-chord 'elements)))))
1593    (else #f)))
1594
1595 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1596
1597 (define-public (map-some-music map? music)
1598   "Walk through @var{music}, transform all elements calling @var{map?}
1599 and only recurse if this returns @code{#f}."
1600   (let loop ((music music))
1601     (or (map? music)
1602         (let ((elt (ly:music-property music 'element))
1603               (elts (ly:music-property music 'elements))
1604               (arts (ly:music-property music 'articulations)))
1605           (if (ly:music? elt)
1606               (set! (ly:music-property music 'element)
1607                     (loop elt)))
1608           (if (pair? elts)
1609               (set! (ly:music-property music 'elements)
1610                     (map loop elts)))
1611           (if (pair? arts)
1612               (set! (ly:music-property music 'articulations)
1613                     (map loop arts)))
1614           music))))
1615
1616 (define-public (extract-music music pred?)
1617   "Return a flat list of all music matching @var{pred?} inside of
1618 @var{music}, not recursing into matches themselves."
1619   (reverse!
1620    (let loop ((music music) (res '()))
1621      (if (pred? music)
1622          (cons music res)
1623          (fold loop
1624                (fold loop
1625                      (let ((elt (ly:music-property music 'element)))
1626                        (if (null? elt)
1627                            res
1628                            (loop elt res)))
1629                      (ly:music-property music 'elements))
1630                (ly:music-property music 'articulations))))))
1631
1632 (define-public (extract-named-music music music-name)
1633   "Return a flat list of all music named @var{music-name} (either a
1634 single event symbol or a list of alternatives) inside of @var{music},
1635 not recursing into matches themselves."
1636   (extract-music
1637    music
1638    (if (cheap-list? music-name)
1639        (lambda (m) (memq (ly:music-property m 'name) music-name))
1640        (lambda (m) (eq? (ly:music-property m 'name) music-name)))))
1641
1642 (define-public (extract-typed-music music type)
1643   "Return a flat list of all music with @var{type} (either a single
1644 type symbol or a list of alternatives) inside of @var{music}, not
1645 recursing into matches themselves."
1646   (extract-music
1647    music
1648    (if (cheap-list? type)
1649        (lambda (m)
1650          (any (lambda (t) (music-is-of-type? m t)) type))
1651        (lambda (m) (music-is-of-type? m type)))))
1652
1653 (define*-public (event-chord-wrap! music #:optional parser)
1654   "Wrap isolated rhythmic events and non-postevent events in
1655 @var{music} inside of an @code{EventChord}.  If the optional
1656 @var{parser} argument is given, chord repeats @samp{q} are expanded
1657 using the default settings.  Otherwise, you need to cater for them
1658 yourself."
1659   (map-some-music
1660    (lambda (m)
1661      (cond ((music-is-of-type? m 'event-chord)
1662             (if (pair? (ly:music-property m 'articulations))
1663                 (begin
1664                   (set! (ly:music-property m 'elements)
1665                         (append (ly:music-property m 'elements)
1666                                 (ly:music-property m 'articulations)))
1667                   (set! (ly:music-property m 'articulations) '())))
1668             m)
1669            ((music-is-of-type? m 'rhythmic-event)
1670             (let ((arts (ly:music-property m 'articulations)))
1671               (if (pair? arts)
1672                   (set! (ly:music-property m 'articulations) '()))
1673               (make-event-chord (cons m arts))))
1674            (else #f)))
1675    (if parser
1676        (expand-repeat-chords!
1677         (cons 'rhythmic-event
1678               (ly:parser-lookup parser '$chord-repeat-events))
1679         music)
1680        music)))
1681
1682 (define-public (event-chord-notes event-chord)
1683   "Return a list of all notes from @var{event-chord}."
1684   (filter
1685     (lambda (m) (eq? 'NoteEvent (ly:music-property m 'name)))
1686     (ly:music-property event-chord 'elements)))
1687
1688 (define-public (event-chord-pitches event-chord)
1689   "Return a list of all pitches from @var{event-chord}."
1690   (map (lambda (x) (ly:music-property x 'pitch))
1691        (event-chord-notes event-chord)))