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