]> git.donarmstrong.com Git - lilypond.git/blob - scm/music-functions.scm
Make chord repeats q ignore <>
[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-set 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-set 'NoteColumn 'horizontal-shift (quotient n 2))
451      (make-grob-property-set 'MultiMeasureRest 'staff-position (if (odd? n) -4 4))))))
452
453 (define-safe-public (make-voice-props-override n)
454   (make-sequential-music
455    (append
456     (map (lambda (x) (make-grob-property-override x 'direction
457                                                   (if (odd? n) -1 1)))
458          direction-polyphonic-grobs)
459     (list
460      (make-property-set 'graceSettings
461                         ;; TODO: take this from voicedGraceSettings or similar.
462                         '((Voice Stem font-size -3)
463                           (Voice Flag font-size -3)
464                           (Voice NoteHead font-size -3)
465                           (Voice TabNoteHead font-size -4)
466                           (Voice Dots font-size -3)
467                           (Voice Stem length-fraction 0.8)
468                           (Voice Stem no-stem-extend #t)
469                           (Voice Beam beam-thickness 0.384)
470                           (Voice Beam length-fraction 0.8)
471                           (Voice Accidental font-size -4)
472                           (Voice AccidentalCautionary font-size -4)
473                           (Voice Script font-size -3)
474                           (Voice Fingering font-size -8)
475                           (Voice StringNumber font-size -8)))
476
477      (make-grob-property-override 'NoteColumn 'horizontal-shift (quotient n 2))
478      (make-grob-property-override 'MultiMeasureRest 'staff-position (if (odd? n) -4 4))))))
479
480 (define-safe-public (make-voice-props-revert)
481   (make-sequential-music
482    (append
483     (map (lambda (x) (make-grob-property-revert x 'direction))
484          direction-polyphonic-grobs)
485     (list (make-property-unset 'graceSettings)
486           (make-grob-property-revert 'NoteColumn 'horizontal-shift)
487           (make-grob-property-revert 'MultiMeasureRest 'staff-position)))))
488
489
490 (define-safe-public (context-spec-music m context #:optional id)
491   "Add \\context CONTEXT = ID to M."
492   (let ((cm (make-music 'ContextSpeccedMusic
493                         'element m
494                         'context-type context)))
495     (if (string? id)
496         (set! (ly:music-property cm 'context-id) id))
497     cm))
498
499 (define-public (descend-to-context m context)
500   "Like @code{context-spec-music}, but only descending."
501   (let ((cm (context-spec-music m context)))
502     (ly:music-set-property! cm 'descend-only #t)
503     cm))
504
505 (define-public (make-non-relative-music mus)
506   (make-music 'UnrelativableMusic
507               'element mus))
508
509 (define-public (make-apply-context func)
510   (make-music 'ApplyContext
511               'procedure func))
512
513 (define-public (make-sequential-music elts)
514   (make-music 'SequentialMusic
515               'elements elts))
516
517 (define-public (make-simultaneous-music elts)
518   (make-music 'SimultaneousMusic
519               'elements elts))
520
521 (define-safe-public (make-event-chord elts)
522   (make-music 'EventChord
523               'elements elts))
524
525 (define-public (make-skip-music dur)
526   (make-music 'SkipMusic
527               'duration dur))
528
529 (define-public (make-grace-music music)
530   (make-music 'GraceMusic
531               'element music))
532
533 ;;;;;;;;;;;;;;;;
534
535 ;; mmrest
536 (define-public (make-multi-measure-rest duration location)
537   (make-music 'MultiMeasureRestMusic
538               'origin location
539               'duration duration))
540
541 (define-public (make-property-set sym val)
542   (make-music 'PropertySet
543               'symbol sym
544               'value val))
545
546 (define-public (make-property-unset sym)
547   (make-music 'PropertyUnset
548               'symbol sym))
549
550 (define-safe-public (make-articulation name)
551   (make-music 'ArticulationEvent
552               'articulation-type name))
553
554 (define-public (make-lyric-event string duration)
555   (make-music 'LyricEvent
556               'duration duration
557               'text string))
558
559 (define-safe-public (make-span-event type span-dir)
560   (make-music type
561               'span-direction span-dir))
562
563 (define-public (override-head-style heads style)
564   "Override style for @var{heads} to @var{style}."
565   (make-sequential-music
566     (if (pair? heads)
567         (map (lambda (h)
568               (make-grob-property-override h 'style style))
569          heads)
570         (list (make-grob-property-override heads 'style style)))))
571
572 (define-public (revert-head-style heads)
573   "Revert style for @var{heads}."
574   (make-sequential-music
575     (if (pair? heads)
576         (map (lambda (h)
577               (make-grob-property-revert h 'style))
578          heads)
579         (list (make-grob-property-revert heads 'style)))))
580
581 (define-public (style-note-heads heads style music)
582  "Set @var{style} for all @var{heads} in @var{music}.  Works both
583 inside of and outside of chord construct."
584   ;; are we inside a <...>?
585   (if (eq? (ly:music-property music 'name) 'NoteEvent)
586       ;; yes -> use a tweak
587       (begin
588         (set! (ly:music-property music 'tweaks)
589               (acons 'style style (ly:music-property music 'tweaks)))
590         music)
591       ;; not in <...>, so use overrides
592       (make-sequential-music
593         (list
594           (override-head-style heads style)
595           music
596           (revert-head-style heads)))))
597
598  (define-public (set-mus-properties! m alist)
599   "Set all of @var{alist} as properties of @var{m}."
600   (if (pair? alist)
601       (begin
602         (set! (ly:music-property m (caar alist)) (cdar alist))
603         (set-mus-properties! m (cdr alist)))))
604
605 (define-public (music-separator? m)
606   "Is @var{m} a separator?"
607   (let ((ts (ly:music-property m 'types)))
608     (memq 'separator ts)))
609
610 ;;; expanding repeat chords
611 (define-public (copy-repeat-chord original-chord repeat-chord duration
612                                   event-types)
613   "Copies all events in @var{event-types} (be sure to include
614 @code{rhythmic-events}) from @var{original-chord} over to
615 @var{repeat-chord} with their articulations filtered as well.  Any
616 duration is replaced with the specified @var{duration}."
617   ;; First remove everything from event-types that can already be
618   ;; found in the repeated chord.  We don't need to look for
619   ;; articulations on individual events since they can't actually get
620   ;; into a repeat chord given its input syntax.
621   (for-each (lambda (e)
622               (for-each (lambda (x)
623                           (set! event-types (delq x event-types)))
624                         (ly:music-property e 'types)))
625             (ly:music-property repeat-chord 'elements))
626   ;; now treat the elements
627   (set! (ly:music-property repeat-chord 'elements)
628         (append!
629          (filter-map
630           (lambda (m)
631             (and (any (lambda (t) (music-is-of-type? m t)) event-types)
632                  (begin
633                    (set! m (ly:music-deep-copy m))
634                    (if (pair? (ly:music-property m 'articulations))
635                        (set! (ly:music-property m 'articulations)
636                              (filter
637                               (lambda (a)
638                                 (any (lambda (t) (music-is-of-type? a t))
639                                      event-types))
640                               (ly:music-property m 'articulations))))
641                    (if (ly:duration? (ly:music-property m 'duration))
642                        (set! (ly:music-property m 'duration) duration))
643                    m)))
644           (ly:music-property original-chord 'elements))
645          (ly:music-property repeat-chord 'elements))))
646
647 (define-public (expand-repeat-chords! event-types music)
648   "Walks through @var{music} and fills repeated chords (notable by
649 having a duration in @code{duration}) with the notes from their
650 respective predecessor chord."
651   (let loop ((music music) (last-chord #f))
652     (if (music-is-of-type? music 'event-chord)
653         (let ((chord-repeat (ly:music-property music 'duration)))
654           (cond
655            ((not (ly:duration? chord-repeat))
656             (if (any (lambda (m) (ly:duration?
657                                   (ly:music-property m 'duration)))
658                      (ly:music-property music 'elements))
659                 music
660                 last-chord))
661            (last-chord
662             (set! (ly:music-property music 'duration) '())
663             (copy-repeat-chord last-chord music chord-repeat event-types)
664             music)
665            (else
666             (ly:music-warning music (_ "Bad chord repetition"))
667             #f)))
668         (let ((elt (ly:music-property music 'element)))
669           (fold loop (if (ly:music? elt) (loop elt last-chord) last-chord)
670                 (ly:music-property music 'elements)))))
671   music)
672
673 ;;; splitting chords into voices.
674 (define (voicify-list lst number)
675   "Make a list of Musics.
676
677 voicify-list :: [ [Music ] ] -> number -> [Music]
678 LST is a list music-lists.
679
680 NUMBER is 0-base, i.e., Voice=1 (upstems) has number 0.
681 "
682   (if (null? lst)
683       '()
684       (cons (context-spec-music
685              (make-sequential-music
686               (list (make-voice-props-set number)
687                     (make-simultaneous-music (car lst))))
688              'Bottom  (number->string (1+ number)))
689             (voicify-list (cdr lst) (1+ number)))))
690
691 (define (voicify-chord ch)
692   "Split the parts of a chord into different Voices using separator"
693   (let ((es (ly:music-property ch 'elements)))
694     (set! (ly:music-property  ch 'elements)
695           (voicify-list (split-list-by-separator es music-separator?) 0))
696     ch))
697
698 (define-public (voicify-music m)
699   "Recursively split chords that are separated with @code{\\\\}."
700   (if (not (ly:music? m))
701       (ly:error (_ "music expected: ~S") m))
702   (let ((es (ly:music-property m 'elements))
703         (e (ly:music-property m 'element)))
704
705     (if (pair? es)
706         (set! (ly:music-property m 'elements) (map voicify-music es)))
707     (if (ly:music? e)
708         (set! (ly:music-property m 'element)  (voicify-music e)))
709     (if (and (equal? (ly:music-property m 'name) 'SimultaneousMusic)
710              (reduce (lambda (x y ) (or x y)) #f (map music-separator? es)))
711         (set! m (context-spec-music (voicify-chord m) 'Staff)))
712     m))
713
714 (define-public (empty-music)
715   (make-music 'Music))
716
717 ;; Make a function that checks score element for being of a specific type.
718 (define-public (make-type-checker symbol)
719   (lambda (elt)
720     (grob::has-interface elt symbol)))
721
722 (define-public ((outputproperty-compatibility func sym val) grob g-context ao-context)
723   (if (func grob)
724       (set! (ly:grob-property grob sym) val)))
725
726
727 (define-public ((set-output-property grob-name symbol val)  grob grob-c context)
728   "Usage example:
729 @code{\\applyoutput #(set-output-property 'Clef 'extra-offset '(0 . 1))}"
730   (let ((meta (ly:grob-property grob 'meta)))
731     (if (equal? (assoc-get 'name meta) grob-name)
732         (set! (ly:grob-property grob symbol) val))))
733
734
735 (define-public (skip->rest mus)
736   "Replace @var{mus} by @code{RestEvent} of the same duration if it is a
737 @code{SkipEvent}.  Useful for extracting parts from crowded scores."
738
739   (if  (memq (ly:music-property mus 'name) '(SkipEvent SkipMusic))
740    (make-music 'RestEvent 'duration (ly:music-property mus 'duration))
741    mus))
742
743
744 (define-public (music-has-type music type)
745   (memq type (ly:music-property music 'types)))
746
747 (define-public (music-clone music)
748   (define (alist->args alist acc)
749     (if (null? alist)
750         acc
751         (alist->args (cdr alist)
752                      (cons (caar alist) (cons (cdar alist) acc)))))
753
754   (apply
755    make-music
756    (ly:music-property music 'name)
757    (alist->args (ly:music-mutable-properties music) '())))
758
759 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
760 ;; warn for bare chords at start.
761
762 (define-public (ly:music-message music msg)
763   (let ((ip (ly:music-property music 'origin)))
764     (if (ly:input-location? ip)
765         (ly:input-message ip msg)
766         (ly:message msg))))
767
768 (define-public (ly:music-warning music msg)
769   (let ((ip (ly:music-property music 'origin)))
770     (if (ly:input-location? ip)
771         (ly:input-warning ip msg)
772         (ly:warning msg))))
773
774 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
775 ;;
776 ;; setting stuff for grace context.
777 ;;
778
779 (define (vector-extend v x)
780   "Make a new vector consisting of V, with X added to the end."
781   (let* ((n (vector-length v))
782          (nv (make-vector (+ n 1) '())))
783     (vector-move-left! v 0 n nv 0)
784     (vector-set! nv n x)
785     nv))
786
787 (define (vector-map f v)
788   "Map F over V.  This function returns nothing."
789   (do ((n (vector-length v))
790        (i 0 (+ i 1)))
791       ((>= i n))
792     (f (vector-ref v i))))
793
794 (define (vector-reverse-map f v)
795   "Map F over V, N to 0 order.  This function returns nothing."
796   (do ((i (- (vector-length v) 1) (- i 1)))
797       ((< i 0))
798     (f (vector-ref v i))))
799
800 (define-public (add-grace-property context-name grob sym val)
801   "Set @var{sym}=@var{val} for @var{grob} in @var{context-name}."
802   (define (set-prop context)
803     (let* ((where (ly:context-property-where-defined context 'graceSettings))
804            (current (ly:context-property where 'graceSettings))
805            (new-settings (append current
806                                  (list (list context-name grob sym val)))))
807       (ly:context-set-property! where 'graceSettings new-settings)))
808   (context-spec-music (make-apply-context set-prop) 'Voice))
809
810 (define-public (remove-grace-property context-name grob sym)
811   "Remove all @var{sym} for @var{grob} in @var{context-name}."
812   (define (sym-grob-context? property sym grob context-name)
813     (and (eq? (car property) context-name)
814          (eq? (cadr property) grob)
815          (eq? (caddr property) sym)))
816   (define (delete-prop context)
817     (let* ((where (ly:context-property-where-defined context 'graceSettings))
818            (current (ly:context-property where 'graceSettings))
819            (prop-settings (filter
820                             (lambda(x) (sym-grob-context? x sym grob context-name))
821                             current))
822            (new-settings current))
823       (for-each (lambda(x)
824                  (set! new-settings (delete x new-settings)))
825                prop-settings)
826       (ly:context-set-property! where 'graceSettings new-settings)))
827   (context-spec-music (make-apply-context delete-prop) 'Voice))
828
829
830
831 (defmacro-public def-grace-function (start stop . docstring)
832   "Helper macro for defining grace music"
833   `(define-music-function (parser location music) (ly:music?)
834      ,@docstring
835      (make-music 'GraceMusic
836                  'origin location
837                  'element (make-music 'SequentialMusic
838                                       'elements (list (ly:music-deep-copy ,start)
839                                                       music
840                                                       (ly:music-deep-copy ,stop))))))
841
842 (defmacro-public define-syntax-function (type args signature . body)
843   "Helper macro for `ly:make-music-function'.
844 Syntax:
845   (define-syntax-function (result-type? parser location arg1 arg2 ...) (result-type? arg1-type arg2-type ...)
846     ...function body...)
847
848 argX-type can take one of the forms @code{predicate?} for mandatory
849 arguments satisfying the predicate, @code{(predicate?)} for optional
850 parameters of that type defaulting to @code{#f}, @code{@w{(predicate?
851 value)}} for optional parameters with a specified default
852 value (evaluated at definition time).  An optional parameter can be
853 omitted in a call only when it can't get confused with a following
854 parameter of different type.
855
856 Predicates with syntactical significance are @code{ly:pitch?},
857 @code{ly:duration?}, @code{ly:music?}, @code{markup?}.  Other
858 predicates require the parameter to be entered as Scheme expression.
859
860 @code{result-type?} can specify a default in the same manner as
861 predicates, to be used in case of a type error in arguments or
862 result."
863
864   (set! signature (map (lambda (pred)
865                          (if (pair? pred)
866                              `(cons ,(car pred)
867                                     ,(and (pair? (cdr pred)) (cadr pred)))
868                              pred))
869                        (cons type signature)))
870   (if (and (pair? body) (pair? (car body)) (eqv? '_i (caar body)))
871       ;; When the music function definition contains a i10n doc string,
872       ;; (_i "doc string"), keep the literal string only
873       (let ((docstring (cadar body))
874             (body (cdr body)))
875         `(ly:make-music-function (list ,@signature)
876                                  (lambda ,args
877                                    ,docstring
878                                    ,@body)))
879       `(ly:make-music-function (list ,@signature)
880                                (lambda ,args
881                                  ,@body))))
882
883 (defmacro-public define-music-function rest
884   "Defining macro returning music functions.
885 Syntax:
886   (define-music-function (parser location arg1 arg2 ...) (arg1-type? arg2-type? ...)
887     ...function body...)
888
889 argX-type can take one of the forms @code{predicate?} for mandatory
890 arguments satisfying the predicate, @code{(predicate?)} for optional
891 parameters of that type defaulting to @code{#f}, @code{@w{(predicate?
892 value)}} for optional parameters with a specified default
893 value (evaluated at definition time).  An optional parameter can be
894 omitted in a call only when it can't get confused with a following
895 parameter of different type.
896
897 Predicates with syntactical significance are @code{ly:pitch?},
898 @code{ly:duration?}, @code{ly:music?}, @code{markup?}.  Other
899 predicates require the parameter to be entered as Scheme expression.
900
901 Must return a music expression.  The @code{origin} is automatically
902 set to the @code{location} parameter."
903
904   `(define-syntax-function (ly:music? (make-music 'Music 'void #t)) ,@rest))
905
906
907 (defmacro-public define-scheme-function rest
908   "Defining macro returning Scheme functions.
909 Syntax:
910   (define-scheme-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 Can return arbitrary expressions.  If a music expression is returned,
926 its @code{origin} is automatically set to the @code{location}
927 parameter."
928
929   `(define-syntax-function scheme? ,@rest))
930
931 (defmacro-public define-void-function rest
932   "This defines a Scheme function like @code{define-scheme-function} with
933 void return value (i.e., what most Guile functions with `unspecified'
934 value return).  Use this when defining functions for executing actions
935 rather than returning values, to keep Lilypond from trying to interpret
936 the return value."
937   `(define-syntax-function (void? *unspecified*) ,@rest *unspecified*))
938
939 (defmacro-public define-event-function rest
940   "Defining macro returning event functions.
941 Syntax:
942   (define-event-function (parser location arg1 arg2 ...) (arg1-type? arg2-type? ...)
943     ...function body...)
944
945 argX-type can take one of the forms @code{predicate?} for mandatory
946 arguments satisfying the predicate, @code{(predicate?)} for optional
947 parameters of that type defaulting to @code{#f}, @code{@w{(predicate?
948 value)}} for optional parameters with a specified default
949 value (evaluated at definition time).  An optional parameter can be
950 omitted in a call only when it can't get confused with a following
951 parameter of different type.
952
953 Predicates with syntactical significance are @code{ly:pitch?},
954 @code{ly:duration?}, @code{ly:music?}, @code{markup?}.  Other
955 predicates require the parameter to be entered as Scheme expression.
956
957 Must return an event expression.  The @code{origin} is automatically
958 set to the @code{location} parameter."
959
960   `(define-syntax-function (ly:event? (make-music 'Event 'void #t)) ,@rest))
961
962 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
963
964 (define-public (cue-substitute quote-music)
965   "Must happen after @code{quote-substitute}."
966
967   (if (vector? (ly:music-property quote-music 'quoted-events))
968       (let* ((dir (ly:music-property quote-music 'quoted-voice-direction))
969              (clef (ly:music-property quote-music 'quoted-music-clef))
970              (main-voice (if (eq? 1 dir) 1 0))
971              (cue-voice (if (eq? 1 dir) 0 1))
972              (main-music (ly:music-property quote-music 'element))
973              (return-value quote-music))
974
975         (if (or (eq? 1 dir) (eq? -1 dir))
976
977             ;; if we have stem dirs, change both quoted and main music
978             ;; to have opposite stems.
979             (begin
980               (set! return-value
981                     ;; cannot context-spec Quote-music, since context
982                     ;; for the quotes is determined in the iterator.
983                     (make-sequential-music
984                      (list
985                       (if (null? clef)
986                           (make-music 'Music)
987                           (make-cue-clef-set clef))
988                       (context-spec-music (make-voice-props-override cue-voice) 'CueVoice "cue")
989                       quote-music
990                       (context-spec-music (make-voice-props-revert) 'CueVoice "cue")
991                       (if (null? clef)
992                           (make-music 'Music)
993                           (make-cue-clef-unset)))))
994               (set! main-music
995                     (make-sequential-music
996                      (list
997                       (make-voice-props-override main-voice)
998                       main-music
999                       (make-voice-props-revert))))
1000               (set! (ly:music-property quote-music 'element) main-music)))
1001
1002         return-value)
1003       quote-music))
1004
1005 (define-public ((quote-substitute quote-tab) music)
1006   (let* ((quoted-name (ly:music-property music 'quoted-music-name))
1007          (quoted-vector (and (string? quoted-name)
1008                              (hash-ref quote-tab quoted-name #f))))
1009
1010
1011     (if (string? quoted-name)
1012         (if (vector? quoted-vector)
1013             (begin
1014               (set! (ly:music-property music 'quoted-events) quoted-vector)
1015               (set! (ly:music-property music 'iterator-ctor)
1016                     ly:quote-iterator::constructor))
1017             (ly:music-warning music (ly:format (_ "cannot find quoted music: `~S'") quoted-name))))
1018     music))
1019
1020
1021 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1022 ;; switch it on here, so parsing and init isn't checked (too slow!)
1023 ;;
1024 ;; automatic music transformations.
1025
1026 (define (switch-on-debugging m)
1027   (if (defined? 'set-debug-cell-accesses!)
1028       (set-debug-cell-accesses! 15000))
1029   m)
1030
1031 (define (music-check-error music)
1032   (define found #f)
1033   (define (signal m)
1034     (if (and (ly:music? m)
1035              (eq? (ly:music-property m 'error-found) #t))
1036         (set! found #t)))
1037
1038   (for-each signal (ly:music-property music 'elements))
1039   (signal (ly:music-property music 'element))
1040
1041   (if found
1042       (set! (ly:music-property music 'error-found) #t))
1043   music)
1044
1045 (define (precompute-music-length music)
1046   (set! (ly:music-property music 'length)
1047         (ly:music-length music))
1048   music)
1049
1050 (define-public (make-duration-of-length moment)
1051  "Make duration of the given @code{moment} length."
1052  (ly:make-duration 0 0
1053   (ly:moment-main-numerator moment)
1054   (ly:moment-main-denominator moment)))
1055
1056 (define (make-skipped moment bool)
1057  "Depending on BOOL, set or unset skipTypesetting,
1058 then make SkipMusic of the given MOMENT length, and
1059 then revert skipTypesetting."
1060  (make-sequential-music
1061   (list
1062    (context-spec-music (make-property-set 'skipTypesetting bool)
1063     'Score)
1064    (make-music 'SkipMusic 'duration
1065     (make-duration-of-length moment))
1066    (context-spec-music (make-property-set 'skipTypesetting (not bool))
1067     'Score))))
1068
1069 (define (skip-as-needed music parser)
1070   "Replace MUSIC by
1071  << {  \\set skipTypesetting = ##f
1072  LENGTHOF(\\showFirstLength)
1073  \\set skipTypesetting = ##t
1074  LENGTHOF(\\showLastLength) }
1075  MUSIC >>
1076  if appropriate.
1077
1078  When only showFirstLength is set,
1079  the 'length property of the music is
1080  overridden to speed up compiling."
1081   (let*
1082       ((show-last (ly:parser-lookup parser 'showLastLength))
1083        (show-first (ly:parser-lookup parser 'showFirstLength))
1084        (show-last-length (and (ly:music? show-last)
1085                               (ly:music-length show-last)))
1086        (show-first-length (and (ly:music? show-first)
1087                                (ly:music-length show-first)))
1088        (orig-length (ly:music-length music)))
1089
1090     ;;FIXME: if using either showFirst- or showLastLength,
1091     ;; make sure that skipBars is not set.
1092
1093     (cond
1094
1095      ;; both properties may be set.
1096      ((and show-first-length show-last-length)
1097       (let
1098           ((skip-length (ly:moment-sub orig-length show-last-length)))
1099         (make-simultaneous-music
1100          (list
1101           (make-sequential-music
1102            (list
1103             (make-skipped skip-length #t)
1104             ;; let's draw a separator between the beginning and the end
1105             (context-spec-music (make-property-set 'whichBar "||")
1106                                 'Timing)))
1107           (make-skipped show-first-length #f)
1108           music))))
1109
1110      ;; we may only want to print the last length
1111      (show-last-length
1112       (let
1113           ((skip-length (ly:moment-sub orig-length show-last-length)))
1114         (make-simultaneous-music
1115          (list
1116           (make-skipped skip-length #t)
1117           music))))
1118
1119      ;; we may only want to print the beginning; in this case
1120      ;; only the first length will be processed (much faster).
1121      (show-first-length
1122       ;; the first length must not exceed the original length.
1123       (if (ly:moment<? show-first-length orig-length)
1124           (set! (ly:music-property music 'length)
1125                 show-first-length))
1126       music)
1127
1128      (else music))))
1129
1130
1131 (define-public toplevel-music-functions
1132   (list
1133    (lambda (music parser) (expand-repeat-chords!
1134                            (cons 'rhythmic-event
1135                                  (ly:parser-lookup parser '$chord-repeat-events))
1136                            music))
1137    (lambda (music parser) (voicify-music music))
1138    (lambda (x parser) (music-map music-check-error x))
1139    (lambda (x parser) (music-map precompute-music-length x))
1140    (lambda (music parser)
1141
1142      (music-map (quote-substitute (ly:parser-lookup parser 'musicQuotes))  music))
1143
1144    ;; switch-on-debugging
1145    (lambda (x parser) (music-map cue-substitute x))
1146
1147    (lambda (x parser)
1148      (skip-as-needed x parser)
1149    )))
1150
1151 ;;;;;;;;;;
1152 ;;; general purpose music functions
1153
1154 (define (shift-octave pitch octave-shift)
1155   (_i "Add @var{octave-shift} to the octave of @var{pitch}.")
1156   (ly:make-pitch
1157      (+ (ly:pitch-octave pitch) octave-shift)
1158      (ly:pitch-notename pitch)
1159      (ly:pitch-alteration pitch)))
1160
1161
1162 ;;;;;;;;;;;;;;;;;
1163 ;; lyrics
1164
1165 (define (apply-durations lyric-music durations)
1166   (define (apply-duration music)
1167     (if (and (not (equal? (ly:music-length music) ZERO-MOMENT))
1168              (ly:duration?  (ly:music-property music 'duration)))
1169         (begin
1170           (set! (ly:music-property music 'duration) (car durations))
1171           (set! durations (cdr durations)))))
1172
1173   (music-map apply-duration lyric-music))
1174
1175
1176 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1177 ;; accidentals
1178
1179 (define (recent-enough? bar-number alteration-def laziness)
1180   (or (number? alteration-def)
1181       (equal? laziness #t)
1182       (<= bar-number (+ (cadr alteration-def) laziness))))
1183
1184 (define (accidental-invalid? alteration-def)
1185   "Checks an alteration entry for being invalid.
1186
1187 Non-key alterations are invalidated when tying into the next bar or
1188 when there is a clef change, since neither repetition nor cancellation
1189 can be omitted when the same note occurs again.
1190
1191 Returns @code{#f} or the reason for the invalidation, a symbol."
1192   (let* ((def (if (pair? alteration-def)
1193                   (car alteration-def)
1194                   alteration-def)))
1195     (and (symbol? def) def)))
1196
1197 (define (extract-alteration alteration-def)
1198   (cond ((number? alteration-def)
1199          alteration-def)
1200         ((pair? alteration-def)
1201          (car alteration-def))
1202         (else 0)))
1203
1204 (define (check-pitch-against-signature context pitch barnum laziness octaveness)
1205   "Checks the need for an accidental and a @q{restore} accidental against
1206 @code{localKeySignature}.  The @var{laziness} is the number of measures
1207 for which reminder accidentals are used (i.e., if @var{laziness} is zero,
1208 only cancel accidentals in the same measure; if @var{laziness} is three,
1209 we cancel accidentals up to three measures after they first appear.
1210 @var{octaveness} is either @code{'same-octave} or @code{'any-octave} and
1211 specifies whether accidentals should be canceled in different octaves."
1212   (let* ((ignore-octave (cond ((equal? octaveness 'any-octave) #t)
1213                               ((equal? octaveness 'same-octave) #f)
1214                               (else
1215                                (ly:warning (_ "Unknown octaveness type: ~S ") octaveness)
1216                                (ly:warning (_ "Defaulting to 'any-octave."))
1217                                #t)))
1218          (key-sig (ly:context-property context 'keySignature))
1219          (local-key-sig (ly:context-property context 'localKeySignature))
1220          (notename (ly:pitch-notename pitch))
1221          (octave (ly:pitch-octave pitch))
1222          (pitch-handle (cons octave notename))
1223          (need-restore #f)
1224          (need-accidental #f)
1225          (previous-alteration #f)
1226          (from-other-octaves #f)
1227          (from-same-octave (assoc-get pitch-handle local-key-sig))
1228          (from-key-sig (or (assoc-get notename local-key-sig)
1229
1230     ;; If no key signature match is found from localKeySignature, we may have a custom
1231     ;; type with octave-specific entries of the form ((octave . pitch) alteration)
1232     ;; instead of (pitch . alteration).  Since this type cannot coexist with entries in
1233     ;; localKeySignature, try extracting from keySignature instead.
1234                            (assoc-get pitch-handle key-sig))))
1235
1236     ;; loop through localKeySignature to search for a notename match from other octaves
1237     (let loop ((l local-key-sig))
1238       (if (pair? l)
1239           (let ((entry (car l)))
1240             (if (and (pair? (car entry))
1241                      (= (cdar entry) notename))
1242                 (set! from-other-octaves (cdr entry))
1243                 (loop (cdr l))))))
1244
1245     ;; find previous alteration-def for comparison with pitch
1246     (cond
1247      ;; from same octave?
1248      ((and (not ignore-octave)
1249            from-same-octave
1250            (recent-enough? barnum from-same-octave laziness))
1251       (set! previous-alteration from-same-octave))
1252
1253      ;; from any octave?
1254      ((and ignore-octave
1255            from-other-octaves
1256            (recent-enough? barnum from-other-octaves laziness))
1257       (set! previous-alteration from-other-octaves))
1258
1259      ;; not recent enough, extract from key signature/local key signature
1260      (from-key-sig
1261       (set! previous-alteration from-key-sig)))
1262
1263     (if (accidental-invalid? previous-alteration)
1264         (set! need-accidental #t)
1265
1266         (let* ((prev-alt (extract-alteration previous-alteration))
1267                (this-alt (ly:pitch-alteration pitch)))
1268
1269           (if (not (= this-alt prev-alt))
1270               (begin
1271                 (set! need-accidental #t)
1272                 (if (and (not (= this-alt 0))
1273                          (and (< (abs this-alt) (abs prev-alt))
1274                              (> (* prev-alt this-alt) 0)))
1275                     (set! need-restore #t))))))
1276
1277     (cons need-restore need-accidental)))
1278
1279 (define-public ((make-accidental-rule octaveness laziness) context pitch barnum measurepos)
1280   "Create an accidental rule that makes its decision based on the octave of
1281 the note and a laziness value.
1282
1283 @var{octaveness} is either @code{'same-octave} or @code{'any-octave} and
1284 defines whether the rule should respond to accidental changes in other
1285 octaves than the current.  @code{'same-octave} is the normal way to typeset
1286 accidentals -- an accidental is made if the alteration is different from the
1287 last active pitch in the same octave.  @code{'any-octave} looks at the last
1288 active pitch in any octave.
1289
1290 @var{laziness} states over how many bars an accidental should be remembered.
1291 @code{0}@tie{}is the default -- accidental lasts over 0@tie{}bar lines, that
1292 is, to the end of current measure.  A positive integer means that the
1293 accidental lasts over that many bar lines.  @w{@code{-1}} is `forget
1294 immediately', that is, only look at key signature.  @code{#t} is `forever'."
1295
1296   (check-pitch-against-signature context pitch barnum laziness octaveness))
1297
1298 (define (key-entry-notename entry)
1299   "Return the pitch of an entry in localKeySignature.  The entry is either of the form
1300   '(notename . alter) or '((octave . notename) . (alter barnum . measurepos))."
1301   (if (number? (car entry))
1302       (car entry)
1303       (cdar entry)))
1304
1305 (define (key-entry-octave entry)
1306   "Return the octave of an entry in localKeySignature (or #f if the entry does not have
1307   an octave)."
1308   (and (pair? (car entry)) (caar entry)))
1309
1310 (define (key-entry-bar-number entry)
1311   "Return the bar number of an entry in localKeySignature (or #f if the entry does not
1312   have a bar number)."
1313   (and (pair? (car entry)) (caddr entry)))
1314
1315 (define (key-entry-measure-position entry)
1316   "Return the measure position of an entry in localKeySignature (or #f if the entry does
1317   not have a measure position)."
1318   (and (pair? (car entry)) (cdddr entry)))
1319
1320 (define (key-entry-alteration entry)
1321   "Return the alteration of an entry in localKeySignature.
1322
1323 For convenience, returns @code{0} if entry is @code{#f}."
1324   (if entry
1325       (if (number? (car entry))
1326           (cdr entry)
1327           (cadr entry))
1328       0))
1329
1330 (define-public (find-pitch-entry keysig pitch accept-global accept-local)
1331   "Return the first entry in @var{keysig} that matches @var{pitch}.
1332 @var{accept-global} states whether key signature entries should be included.
1333 @var{accept-local} states whether local accidentals should be included.
1334 If no matching entry is found, @var{#f} is returned."
1335   (and (pair? keysig)
1336        (let* ((entry (car keysig))
1337               (entryoct (key-entry-octave entry))
1338               (entrynn (key-entry-notename entry))
1339               (oct (ly:pitch-octave pitch))
1340               (nn (ly:pitch-notename pitch)))
1341          (if (and (equal? nn entrynn)
1342                   (or (and accept-global (not entryoct))
1343                       (and accept-local (equal? oct entryoct))))
1344              entry
1345              (find-pitch-entry (cdr keysig) pitch accept-global accept-local)))))
1346
1347 (define-public (neo-modern-accidental-rule context pitch barnum measurepos)
1348   "An accidental rule that typesets an accidental if it differs from the
1349 key signature @emph{and} does not directly follow a note on the same
1350 staff line.  This rule should not be used alone because it does neither
1351 look at bar lines nor different accidentals at the same note name."
1352   (let* ((keysig (ly:context-property context 'localKeySignature))
1353          (entry (find-pitch-entry keysig pitch #t #t)))
1354     (if (not entry)
1355         (cons #f #f)
1356         (let* ((global-entry (find-pitch-entry keysig pitch #t #f))
1357                (key-acc (key-entry-alteration global-entry))
1358                (acc (ly:pitch-alteration pitch))
1359                (entrymp (key-entry-measure-position entry))
1360                (entrybn (key-entry-bar-number entry)))
1361           (cons #f (not (or (equal? acc key-acc)
1362                             (and (equal? entrybn barnum) (equal? entrymp measurepos)))))))))
1363
1364 (define-public (teaching-accidental-rule context pitch barnum measurepos)
1365   "An accidental rule that typesets a cautionary accidental if it is
1366 included in the key signature @emph{and} does not directly follow a note
1367 on the same staff line."
1368   (let* ((keysig (ly:context-property context 'localKeySignature))
1369          (entry (find-pitch-entry keysig pitch #t #t)))
1370     (if (not entry)
1371         (cons #f #f)
1372         (let* ((global-entry (find-pitch-entry keysig pitch #f #f))
1373                (key-acc (key-entry-alteration global-entry))
1374                (acc (ly:pitch-alteration pitch))
1375                (entrymp (key-entry-measure-position entry))
1376                (entrybn (key-entry-bar-number entry)))
1377           (cons #f (not (or (equal? acc key-acc)
1378                             (and (equal? entrybn barnum) (equal? entrymp measurepos)))))))))
1379
1380 (define-public (set-accidentals-properties extra-natural
1381                                            auto-accs auto-cauts
1382                                            context)
1383   (context-spec-music
1384    (make-sequential-music
1385     (append (if (boolean? extra-natural)
1386                 (list (make-property-set 'extraNatural extra-natural))
1387                 '())
1388             (list (make-property-set 'autoAccidentals auto-accs)
1389                   (make-property-set 'autoCautionaries auto-cauts))))
1390    context))
1391
1392 (define-public (set-accidental-style style . rest)
1393   "Set accidental style to @var{style}.  Optionally take a context
1394 argument, e.g. @code{'Staff} or @code{'Voice}.  The context defaults
1395 to @code{Staff}, except for piano styles, which use @code{GrandStaff}
1396 as a context."
1397   (let ((context (if (pair? rest)
1398                      (car rest) 'Staff))
1399         (pcontext (if (pair? rest)
1400                       (car rest) 'GrandStaff)))
1401     (cond
1402       ;; accidentals as they were common in the 18th century.
1403       ((equal? style 'default)
1404        (set-accidentals-properties #t
1405                                    `(Staff ,(make-accidental-rule 'same-octave 0))
1406                                    '()
1407                                    context))
1408       ;; accidentals from one voice do NOT get canceled in other voices
1409       ((equal? style 'voice)
1410        (set-accidentals-properties #t
1411                                    `(Voice ,(make-accidental-rule 'same-octave 0))
1412                                    '()
1413                                    context))
1414       ;; accidentals as suggested by Kurt Stone, Music Notation in the 20th century.
1415       ;; This includes all the default accidentals, but accidentals also needs canceling
1416       ;; in other octaves and in the next measure.
1417       ((equal? style 'modern)
1418        (set-accidentals-properties #f
1419                                    `(Staff ,(make-accidental-rule 'same-octave 0)
1420                                            ,(make-accidental-rule 'any-octave 0)
1421                                            ,(make-accidental-rule 'same-octave 1))
1422                                    '()
1423                                    context))
1424       ;; the accidentals that Stone adds to the old standard as cautionaries
1425       ((equal? style 'modern-cautionary)
1426        (set-accidentals-properties #f
1427                                    `(Staff ,(make-accidental-rule 'same-octave 0))
1428                                    `(Staff ,(make-accidental-rule 'any-octave 0)
1429                                            ,(make-accidental-rule 'same-octave 1))
1430                                    context))
1431       ;; same as modern, but accidentals different from the key signature are always
1432       ;; typeset - unless they directly follow a note of the same pitch.
1433       ((equal? style 'neo-modern)
1434        (set-accidentals-properties #f
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                                    '()
1440                                    context))
1441       ((equal? style 'neo-modern-cautionary)
1442        (set-accidentals-properties #f
1443                                    `(Staff ,(make-accidental-rule 'same-octave 0))
1444                                    `(Staff ,(make-accidental-rule 'any-octave 0)
1445                                            ,(make-accidental-rule 'same-octave 1)
1446                                            ,neo-modern-accidental-rule)
1447                                    context))
1448       ((equal? style 'neo-modern-voice)
1449        (set-accidentals-properties #f
1450                                    `(Voice ,(make-accidental-rule 'same-octave 0)
1451                                            ,(make-accidental-rule 'any-octave 0)
1452                                            ,(make-accidental-rule 'same-octave 1)
1453                                            ,neo-modern-accidental-rule
1454                                      Staff ,(make-accidental-rule 'same-octave 0)
1455                                            ,(make-accidental-rule 'any-octave 0)
1456                                            ,(make-accidental-rule 'same-octave 1)
1457                                       ,neo-modern-accidental-rule)
1458                                    '()
1459                                    context))
1460       ((equal? style 'neo-modern-voice-cautionary)
1461        (set-accidentals-properties #f
1462                                    `(Voice ,(make-accidental-rule 'same-octave 0))
1463                                    `(Voice ,(make-accidental-rule 'any-octave 0)
1464                                            ,(make-accidental-rule 'same-octave 1)
1465                                            ,neo-modern-accidental-rule
1466                                      Staff ,(make-accidental-rule 'same-octave 0)
1467                                            ,(make-accidental-rule 'any-octave 0)
1468                                            ,(make-accidental-rule 'same-octave 1)
1469                                            ,neo-modern-accidental-rule)
1470                                    context))
1471       ;; Accidentals as they were common in dodecaphonic music with no tonality.
1472       ;; Each note gets one accidental.
1473       ((equal? style 'dodecaphonic)
1474        (set-accidentals-properties #f
1475                                    `(Staff ,(lambda (c p bn mp) '(#f . #t)))
1476                                    '()
1477                                    context))
1478       ;; Multivoice accidentals to be read both by musicians playing one voice
1479       ;; and musicians playing all voices.
1480       ;; Accidentals are typeset for each voice, but they ARE canceled across voices.
1481       ((equal? style 'modern-voice)
1482        (set-accidentals-properties  #f
1483                                     `(Voice ,(make-accidental-rule 'same-octave 0)
1484                                             ,(make-accidental-rule 'any-octave 0)
1485                                             ,(make-accidental-rule 'same-octave 1)
1486                                       Staff ,(make-accidental-rule 'same-octave 0)
1487                                             ,(make-accidental-rule 'any-octave 0)
1488                                             ,(make-accidental-rule 'same-octave 1))
1489                                     '()
1490                                     context))
1491       ;; same as modernVoiceAccidental eccept that all special accidentals are typeset
1492       ;; as cautionaries
1493       ((equal? style 'modern-voice-cautionary)
1494        (set-accidentals-properties #f
1495                                    `(Voice ,(make-accidental-rule 'same-octave 0))
1496                                    `(Voice ,(make-accidental-rule 'any-octave 0)
1497                                            ,(make-accidental-rule 'same-octave 1)
1498                                      Staff ,(make-accidental-rule 'same-octave 0)
1499                                            ,(make-accidental-rule 'any-octave 0)
1500                                            ,(make-accidental-rule 'same-octave 1))
1501                                    context))
1502       ;; stone's suggestions for accidentals on grand staff.
1503       ;; Accidentals are canceled across the staves in the same grand staff as well
1504       ((equal? style 'piano)
1505        (set-accidentals-properties #f
1506                                    `(Staff ,(make-accidental-rule 'same-octave 0)
1507                                            ,(make-accidental-rule 'any-octave 0)
1508                                            ,(make-accidental-rule 'same-octave 1)
1509                                      GrandStaff
1510                                            ,(make-accidental-rule 'any-octave 0)
1511                                            ,(make-accidental-rule 'same-octave 1))
1512                                    '()
1513                                    pcontext))
1514       ((equal? style 'piano-cautionary)
1515        (set-accidentals-properties #f
1516                                    `(Staff ,(make-accidental-rule 'same-octave 0))
1517                                    `(Staff ,(make-accidental-rule 'any-octave 0)
1518                                            ,(make-accidental-rule 'same-octave 1)
1519                                      GrandStaff
1520                                            ,(make-accidental-rule 'any-octave 0)
1521                                            ,(make-accidental-rule 'same-octave 1))
1522                                    pcontext))
1523
1524       ;; same as modern, but cautionary accidentals are printed for all sharp or flat
1525       ;; tones specified by the key signature.
1526        ((equal? style 'teaching)
1527        (set-accidentals-properties #f
1528                                     `(Staff ,(make-accidental-rule 'same-octave 0))
1529                                     `(Staff ,(make-accidental-rule 'same-octave 1)
1530                                            ,teaching-accidental-rule)
1531                                    context))
1532
1533       ;; do not set localKeySignature when a note alterated differently from
1534       ;; localKeySignature is found.
1535       ;; Causes accidentals to be printed at every note instead of
1536       ;; remembered for the duration of a measure.
1537       ;; accidentals not being remembered, causing accidentals always to
1538       ;; be typeset relative to the time signature
1539       ((equal? style 'forget)
1540        (set-accidentals-properties '()
1541                                    `(Staff ,(make-accidental-rule 'same-octave -1))
1542                                    '()
1543                                    context))
1544       ;; Do not reset the key at the start of a measure.  Accidentals will be
1545       ;; printed only once and are in effect until overridden, possibly many
1546       ;; measures later.
1547       ((equal? style 'no-reset)
1548        (set-accidentals-properties '()
1549                                    `(Staff ,(make-accidental-rule 'same-octave #t))
1550                                    '()
1551                                    context))
1552       (else
1553        (ly:warning (_ "unknown accidental style: ~S") style)
1554        (make-sequential-music '())))))
1555
1556 (define-public (invalidate-alterations context)
1557   "Invalidate alterations in @var{context}.
1558
1559 Elements of @code{'localKeySignature} corresponding to local
1560 alterations of the key signature have the form
1561 @code{'((octave . notename) . (alter barnum . measurepos))}.
1562 Replace them with a version where @code{alter} is set to @code{'clef}
1563 to force a repetition of accidentals.
1564
1565 Entries that conform with the current key signature are not invalidated."
1566   (let* ((keysig (ly:context-property context 'keySignature)))
1567     (set! (ly:context-property context 'localKeySignature)
1568           (map-in-order
1569            (lambda (entry)
1570              (let* ((localalt (key-entry-alteration entry))
1571                     (localoct (key-entry-octave entry)))
1572                (if (or (accidental-invalid? localalt)
1573                        (not localoct)
1574                        (= localalt
1575                           (key-entry-alteration
1576                            (find-pitch-entry
1577                             keysig
1578                             (ly:make-pitch localoct
1579                                            (key-entry-notename entry)
1580                                            0)
1581                             #t #t))))
1582                    entry
1583                    (cons (car entry) (cons 'clef (cddr entry))))))
1584            (ly:context-property context 'localKeySignature)))))
1585
1586 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1587
1588 (define-public (skip-of-length mus)
1589   "Create a skip of exactly the same length as @var{mus}."
1590   (let* ((skip
1591           (make-music
1592            'SkipEvent
1593            'duration (ly:make-duration 0 0))))
1594
1595     (make-event-chord (list (ly:music-compress skip (ly:music-length mus))))))
1596
1597 (define-public (mmrest-of-length mus)
1598   "Create a multi-measure rest of exactly the same length as @var{mus}."
1599
1600   (let* ((skip
1601           (make-multi-measure-rest
1602            (ly:make-duration 0 0) '())))
1603     (ly:music-compress skip (ly:music-length mus))
1604     skip))
1605
1606 (define-public (pitch-of-note event-chord)
1607   (let ((evs (filter (lambda (x)
1608                        (music-has-type x 'note-event))
1609                      (ly:music-property event-chord 'elements))))
1610
1611     (and (pair? evs)
1612          (ly:music-property (car evs) 'pitch))))
1613
1614 (define-public (duration-of-note event-chord)
1615   (cond
1616    ((pair? event-chord)
1617     (or (duration-of-note (car event-chord))
1618         (duration-of-note (cdr event-chord))))
1619    ((ly:music? event-chord)
1620     (let ((dur (ly:music-property event-chord 'duration)))
1621       (if (ly:duration? dur)
1622           dur
1623           (duration-of-note (ly:music-property event-chord 'elements)))))
1624    (else #f)))
1625
1626 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1627
1628 (define-public (map-some-music map? music)
1629   "Walk through @var{music}, transform all elements calling @var{map?}
1630 and only recurse if this returns @code{#f}."
1631   (let loop ((music music))
1632     (or (map? music)
1633         (let ((elt (ly:music-property music 'element))
1634               (elts (ly:music-property music 'elements))
1635               (arts (ly:music-property music 'articulations)))
1636           (if (ly:music? elt)
1637               (set! (ly:music-property music 'element)
1638                     (loop elt)))
1639           (if (pair? elts)
1640               (set! (ly:music-property music 'elements)
1641                     (map loop elts)))
1642           (if (pair? arts)
1643               (set! (ly:music-property music 'articulations)
1644                     (map loop arts)))
1645           music))))
1646
1647 (define-public (for-some-music stop? music)
1648   "Walk through @var{music}, process all elements calling @var{stop?}
1649 and only recurse if this returns @code{#f}."
1650   (let loop ((music music))
1651     (if (not (stop? music))
1652         (let ((elt (ly:music-property music 'element)))
1653           (if (ly:music? elt)
1654               (loop elt))
1655           (for-each loop (ly:music-property music 'elements))
1656           (for-each loop (ly:music-property music 'articulations))))))
1657
1658 (define-public (fold-some-music pred? proc init music)
1659   "This works recursively on music like @code{fold} does on a list,
1660 calling @samp{(@var{pred?} music)} on every music element.  If
1661 @code{#f} is returned for an element, it is processed recursively
1662 with the same initial value of @samp{previous}, otherwise
1663 @samp{(@var{proc} music previous)} replaces @samp{previous}
1664 and no recursion happens.
1665 The top @var{music} is processed using @var{init} for @samp{previous}."
1666   (let loop ((music music) (previous init))
1667     (if (pred? music)
1668         (proc music previous)
1669         (fold loop
1670               (fold loop
1671                     (let ((elt (ly:music-property music 'element)))
1672                       (if (null? elt)
1673                           previous
1674                           (loop elt previous)))
1675                     (ly:music-property music 'elements))
1676               (ly:music-property music 'articulations)))))
1677
1678 (define-public (extract-music music pred?)
1679   "Return a flat list of all music matching @var{pred?} inside of
1680 @var{music}, not recursing into matches themselves."
1681   (reverse! (fold-some-music pred? cons '() music)))
1682
1683 (define-public (extract-named-music music music-name)
1684   "Return a flat list of all music named @var{music-name} (either a
1685 single event symbol or a list of alternatives) inside of @var{music},
1686 not recursing into matches themselves."
1687   (extract-music
1688    music
1689    (if (cheap-list? music-name)
1690        (lambda (m) (memq (ly:music-property m 'name) music-name))
1691        (lambda (m) (eq? (ly:music-property m 'name) music-name)))))
1692
1693 (define-public (extract-typed-music music type)
1694   "Return a flat list of all music with @var{type} (either a single
1695 type symbol or a list of alternatives) inside of @var{music}, not
1696 recursing into matches themselves."
1697   (extract-music
1698    music
1699    (if (cheap-list? type)
1700        (lambda (m)
1701          (any (lambda (t) (music-is-of-type? m t)) type))
1702        (lambda (m) (music-is-of-type? m type)))))
1703
1704 (define*-public (event-chord-wrap! music #:optional parser)
1705   "Wrap isolated rhythmic events and non-postevent events in
1706 @var{music} inside of an @code{EventChord}.  If the optional
1707 @var{parser} argument is given, chord repeats @samp{q} are expanded
1708 using the default settings.  Otherwise, you need to cater for them
1709 yourself."
1710   (map-some-music
1711    (lambda (m)
1712      (cond ((music-is-of-type? m 'event-chord)
1713             (if (pair? (ly:music-property m 'articulations))
1714                 (begin
1715                   (set! (ly:music-property m 'elements)
1716                         (append (ly:music-property m 'elements)
1717                                 (ly:music-property m 'articulations)))
1718                   (set! (ly:music-property m 'articulations) '())))
1719             m)
1720            ((music-is-of-type? m 'rhythmic-event)
1721             (let ((arts (ly:music-property m 'articulations)))
1722               (if (pair? arts)
1723                   (set! (ly:music-property m 'articulations) '()))
1724               (make-event-chord (cons m arts))))
1725            (else #f)))
1726    (if parser
1727        (expand-repeat-chords!
1728         (cons 'rhythmic-event
1729               (ly:parser-lookup parser '$chord-repeat-events))
1730         music)
1731        music)))
1732
1733 (define-public (event-chord-notes event-chord)
1734   "Return a list of all notes from @var{event-chord}."
1735   (filter
1736     (lambda (m) (eq? 'NoteEvent (ly:music-property m 'name)))
1737     (ly:music-property event-chord 'elements)))
1738
1739 (define-public (event-chord-pitches event-chord)
1740   "Return a list of all pitches from @var{event-chord}."
1741   (map (lambda (x) (ly:music-property x 'pitch))
1742        (event-chord-notes event-chord)))