* input/regression/beam-quanting-horizontal.ly: update texidoc
[lilypond.git] / scm / music-functions.scm
blob266b0d66d196f0f7ea897a47a07fd6cac0f743e0
2 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
4 (define-public (music-map function music)
5   "Apply @var{function} to @var{music} and all of the music it contains. "
6   (let* ((es (ly:get-mus-property music 'elements))
7          (e (ly:get-mus-property music 'element))
8          )
10     (ly:set-mus-property! music 'elements 
11         (map (lambda (y) (music-map  function y)) es))
12         (if (ly:music? e)
13             (ly:set-mus-property! music 'element (music-map function  e)))
14         (function music)
15         ))
17 (define-public (display-music music)
18   "Display music, not done with music-map for clarity of presentation."
19   (display music)
20   (display ": { ")
21   
22   (let* ((es (ly:get-mus-property music 'elements))
23          (e (ly:get-mus-property music 'element))
24          )
26     (display (ly:get-mutable-properties music))
28     (if (pair?  es)
29         (begin (display "\nElements: {\n")
30                (map display-music es)
31                (display "}\n")
32         ))
33     
34     
35     (if (ly:music? e)
36         (begin
37           (display "\nChild:")
38           (display-music e)
39           )
40         )
41     )
42   (display " }\n")
43   music
44   )
49   
50 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
52 (define (shift-one-duration-log music shift dot)
53   "  add SHIFT to ly:duration-log and optionally 
54   a dot to any note encountered. This scales the music up by a factor 
55   2^shift * (2 - (1/2)^dot)"
57   (let*
58       (
59        (d (ly:get-mus-property music 'duration))
60        )
61     (if (ly:duration? d)
62         (let* (
63                (cp (ly:duration-factor d))
64                (nd (ly:make-duration (+ shift (ly:duration-log d))
65                                      (+ dot (ly:duration-dot-count d))
66                                      (car cp)
67                                      (cdr cp)))
68                
69                )
70           (ly:set-mus-property! music 'duration nd)
71           ))
72     music))
76 (define-public (shift-duration-log music shift dot)
77   (music-map (lambda (x) (shift-one-duration-log x shift dot))
78              music))
79   
83 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
84 ;; repeats.
86 (define-public (unfold-repeats music)
88 This function replaces all repeats  with unfold repeats. It was 
89 written by Rune Zedeler. "
90   (let* ((es (ly:get-mus-property music 'elements))
91          (e (ly:get-mus-property music 'element))
92          (n  (ly:music-name music)))
94     (if (equal? n "Repeated_music")
95         (begin
96           (if (equal?
97                (ly:get-mus-property music 'iterator-ctor)
98                Chord_tremolo_iterator::constructor)
99               (shift-duration-log music  (ly:intlog2 (ly:get-mus-property music 'repeat-count)) 0)
100               )
101           (ly:set-mus-property!
102            music 'length Repeated_music::unfolded_music_length)
103           (ly:set-mus-property!
104            music 'start-moment-function Repeated_music::first_start)
105           (ly:set-mus-property!
106            music 'iterator-ctor Unfolded_repeat_iterator::constructor)))
108     (if (pair? es)
109         (ly:set-mus-property!
110          music 'elements
111          (map unfold-repeats es)))
113     (if (ly:music? e)
114         (ly:set-mus-property!
115          music 'element
116          (unfold-repeats e)))
118     music))
121 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
122 ;; property setting music objs.
124 (define-public (make-grob-property-set grob gprop val)
126   "Make a Music expression that sets GPROP to VAL in GROB. Does a pop first,
127 i.e.  this is not an override"
128   
129    (let* ((m (make-music-by-name  'OverrideProperty)))
130      (ly:set-mus-property! m 'symbol grob)
131      (ly:set-mus-property! m 'grob-property gprop)
132      (ly:set-mus-property! m 'grob-value val)
133      (ly:set-mus-property! m 'pop-first #t)
134                 
135      m
136    
137    ))
140 (define-public (make-grob-property-revert grob gprop)
141   "Revert the grob property GPROP for GROB."
142    (let* ((m (make-music-by-name  'OverrideProperty)))
143      (ly:set-mus-property! m 'symbol grob)
144      (ly:set-mus-property! m 'grob-property gprop)
145                 
146      m
147    
148    ))
151 (define-public (make-voice-props-set n)
152   (make-sequential-music
153    (append
154       (map (lambda (x) (make-grob-property-set x 'direction
155                                                (if (odd? n) -1 1)))
156            '(Tie Slur Stem Dots))
157       (list
158        (make-grob-property-set 'NoteColumn 'horizontal-shift (quotient n 2))
159        (make-grob-property-set 'MultiMeasureRest 'staff-position
160                                (if (odd? n) -4 4)
161                                )
162        
163        )
164    )
165   ))
168 (define-public (make-voice-props-revert)
169   (make-sequential-music
170    (list
171       (make-grob-property-revert 'Tie 'direction)
172       (make-grob-property-revert 'Dots 'direction)
173       (make-grob-property-revert 'Stem 'direction)
174       (make-grob-property-revert 'Slur 'direction)          
175       (make-grob-property-revert 'NoteColumn 'horizontal-shift)
176    ))
177   )
180 (define-public (context-spec-music m context . rest)
181   "Add \context CONTEXT = foo to M. "
182   
183   (let* ((cm (make-music-by-name 'ContextSpeccedMusic)))
184     (ly:set-mus-property! cm 'element m)
185     (ly:set-mus-property! cm 'context-type context)
186     (if (and  (pair? rest) (string? (car rest)))
187         (ly:set-mus-property! cm 'context-id (car rest))
188     )
189     cm
190   ))
192 (define-public (make-apply-context func)
193   (let*
194       (
195        (m (make-music-by-name 'ApplyContext))
196        )
198     (ly:set-mus-property! m 'procedure func)
199     m
200   ))
202 (define-public (make-sequential-music elts)
203   (let*  ((m (make-music-by-name 'SequentialMusic)))
204     (ly:set-mus-property! m 'elements elts)
205     m
206   ))
208 (define-public (make-simultaneous-music elts)
209   (let*  ((m (make-music-by-name 'SimultaneousMusic)))
210     (ly:set-mus-property! m 'elements elts)
211     m
212     ))
214 (define-public (make-event-chord elts)
215   (let*  ((m (make-music-by-name 'EventChord)))
216     (ly:set-mus-property! m 'elements elts)
217     m
218     ))
220 ;;;;;;;;;;;;;;;;
221 ;; mmrest
222 (define-public (make-multi-measure-rest duration location)
223   (let*
224       (
225        (start (make-music-by-name 'MultiMeasureRestEvent))
226        (stop  (make-music-by-name 'MultiMeasureRestEvent))
227        (skip ( make-music-by-name 'SkipEvent))
228        (ch (make-music-by-name 'BarCheck))
229        (ch2  (make-music-by-name 'BarCheck))
230        (seq  (make-music-by-name 'MultiMeasureRestMusicGroup))
231        )
233     (map (lambda (x) (ly:set-mus-property! x 'origin location))
234          (list start stop skip ch ch2 seq))
235     (ly:set-mus-property! start 'span-direction START)
236     (ly:set-mus-property! stop 'span-direction STOP)    
237     (ly:set-mus-property! skip 'duration duration)
238     (ly:set-mus-property! seq 'elements
239      (list
240       ch
241       (make-event-chord (list start))
242       (make-event-chord (list skip))
243       (make-event-chord (list stop))
244       ch2
245       ))
247     seq
248     ))
250 (define-public (glue-mm-rest-texts music)
251   "Check if we have R1*4-\markup { .. }, and if applicable convert to
252 a property set for MultiMeasureRestNumber."
253   
254   (define (script-to-mmrest-text script-music)
255     "Extract 'direction and 'text   from SCRIPT-MUSIC, and transform into property sets."
256     
257     (let*
258         (
259          (text (ly:get-mus-property script-music 'text))
260          (dir (ly:get-mus-property script-music 'direction))
261          (p (make-music-by-name 'MultiMeasureTextEvent))
262          )
264       (if (ly:dir? dir)
265           (ly:set-mus-property! p  'direction dir))
266       (ly:set-mus-property! p 'text text)
267       p
268     ))
269   
270   (if (eq? (ly:get-mus-property music 'name)  'MultiMeasureRestMusicGroup)
271       (let*
272           (
273            (text? (lambda (x) (memq 'script-event (ly:get-mus-property x 'types))))
274            (es (ly:get-mus-property  music 'elements))
275            (texts (map script-to-mmrest-text  (filter-list text? es)))
276            (others (filter-out-list text? es))
277            )
278         (if (pair? texts)
279             (ly:set-mus-property!
280              music 'elements
281              (cons (make-event-chord texts) others)
282             ))
283       ))
284   music
285   )
288 (define-public (make-property-set sym val)
289   (let*
290       (
291        (m (make-music-by-name 'PropertySet))
292        )
293     (ly:set-mus-property! m 'symbol sym)
294     (ly:set-mus-property! m 'value val)
295     m
296   ))
300 (define-public (make-ottava-set octavation)
301   (let*
302       (
303        (m (make-music-by-name 'ApplyContext))
304        )
305     
306   
307   (define (ottava-modify context)
308     "Either reset centralCPosition to the stored original,
309 or remember old centralCPosition, add OCTAVATION to centralCPosition,
310 and set OTTAVATION to `8va', or whatever appropriate."
311     (if (= octavation 0)
312         (let*
313             ((where (ly:context-property-where-defined context 'centralCPosition))
314              (oc0 (ly:get-context-property context 'originalCentralCPosition)) )
316           (ly:set-context-property context 'centralCPosition oc0)
317           (ly:unset-context-property where 'originalCentralCPosition)
318           (ly:unset-context-property where 'ottavation))
320         (let*
321             ((where (ly:context-property-where-defined context 'centralCPosition))
322              (c0 (ly:get-context-property context 'centralCPosition))
323              (new-c0 (+ c0 (* -7 octavation)))
324              (string (cdr
325                       (assoc octavation '((2 . "15ma")
326                                           (1 . "8va")
327                                           (0 . #f)
328                                           (-1 . "8va bassa")
329                                           (-2 . "15ma bassa"))))))
331           (ly:set-context-property context 'centralCPosition new-c0)
332           (ly:set-context-property context 'originalCentralCPosition c0)
333           (ly:set-context-property context 'ottavation string)
334           
335           )))
337   (ly:set-mus-property! m 'procedure  ottava-modify)
338   (context-spec-music m "Staff")
339   ))
341 (define-public (set-octavation ottavation)
342   (ly:export (make-ottava-set ottavation)))
344 (define-public (make-time-signature-set num den . rest)
345   " Set properties for time signature NUM/DEN.
346 Rest can contain a list of beat groupings 
349   
350   (let*
351       (
352        (set1 (make-property-set 'timeSignatureFraction (cons num den) ))
353        (beat (ly:make-moment 1 den))
354        (len  (ly:make-moment num den))
355        (set2 (make-property-set 'beatLength beat))
356        (set3 (make-property-set 'measureLength len))
357        (set4 (make-property-set 'beatGrouping (if (pair? rest)
358                                                   (car rest)
359                                                   '())))
360        (basic  (list set1 set2 set3 set4)))
362     (context-spec-music
363      (make-sequential-music basic) "Timing")))
365 (define-public (set-time-signature num den . rest)
366   (ly:export (apply make-time-signature-set `(,num ,den . ,rest))))
368 (define-public (make-penalty-music pen)
369  (let
370      ((m (make-music-by-name 'BreakEvent)))
371    (ly:set-mus-property! m 'penalty pen)
372    m))
374 (define-public (make-articulation name)
375   (let* (
376          (m (make-music-by-name 'ArticulationEvent))
377       )
378       (ly:set-mus-property! m 'articulation-type name)
379       m
380   ))
382 (define-public (make-span-event type spandir)
383   (let* (
384          (m (make-music-by-name  type))
385          )
386     (ly:set-mus-property! m 'span-direction spandir)
387     m
388     ))
390 (define-public (set-mus-properties! m alist)
391   "Set all of ALIST as properties of M." 
392   (if (pair? alist)
393       (begin
394         (ly:set-mus-property! m (caar alist) (cdar alist))
395         (set-mus-properties! m (cdr alist)))
396   ))
398 (define-public (music-separator? m)
399   "Is M a separator?"
400   (let* ((ts (ly:get-mus-property m 'types )))
401     (memq 'separator ts)
402   ))
405 ;;; splitting chords into voices.
407 (define (voicify-list lst number)
408    "Make a list of Musics.
410    voicify-list :: [ [Music ] ] -> number -> [Music]
411    LST is a list music-lists.
414    (if (null? lst) '()
415        (cons (context-spec-music
416               (make-sequential-music
417                (list
418                 (make-voice-props-set number)
419                 (make-simultaneous-music (car lst))))
421               "Voice"  (number->string number))
422               (voicify-list (cdr lst) (+ number 1))
423        ))
424    )
426 (define (voicify-chord ch)
427   "Split the parts of a chord into different Voices using separator"
428    (let* ((es (ly:get-mus-property ch 'elements)))
431      (ly:set-mus-property!  ch 'elements
432        (voicify-list (split-list es music-separator?) 0))
433      ch
434    ))
436 (define (voicify-music m)
437    "Recursively split chords that are separated with \\ "
438    
439    (if (not (ly:music? m))
440        (begin (display m)
441        (error "not music!"))
442        )
443    (let*
444        ((es (ly:get-mus-property m 'elements))
445         (e (ly:get-mus-property m 'element))
446         )
447      (if (pair? es)
448          (ly:set-mus-property! m 'elements (map voicify-music es)))
449      (if (ly:music? e)
450          (ly:set-mus-property! m 'element  (voicify-music e)))
451      (if
452       (and (equal? (ly:music-name m) "Simultaneous_music")
453            (reduce (lambda (x y ) (or x y))     (map music-separator? es)))
454       (voicify-chord m)
455       )
457      m
458      ))
460 (define-public (empty-music)
461   (ly:export (make-music-by-name 'Music))
462   )
465 ; Make a function that checks score element for being of a specific type. 
466 (define-public (make-type-checker symbol)
467   (lambda (elt)
468     ;;(display  symbol)
469     ;;(eq? #t (ly:get-grob-property elt symbol))
470     (not (eq? #f (memq symbol (ly:get-grob-property elt 'interfaces))))))
474 (define-public (smart-bar-check n)
475   "Make  a bar check that checks for a specific bar number. 
477   (let*
478       (
479        (m (make-music-by-name 'ApplyContext))
480        )
481     
482     (define (checker tr)
483       (let* ((bn (ly:get-context-property tr 'currentBarNumber)))
484         (if (= bn  n)
485             #t
486             (error
487              (format "Bar check failed, we should have reached ~a, instead at ~a\n"
488                      n bn ))
489             )))
491     (ly:set-mus-property! m 'procedure checker)
492     m
493     ))
495 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
496 ;; warn for bare chords at start.
498 (define (has-request-chord elts)
499   (reduce (lambda (x y) (or x y)) (map (lambda (x) (equal? (ly:music-name x)
500                                                            "Request_chord")) elts)
501   ))
503 (define (ly:music-message music msg)
504   (let*
505       (
506       (ip (ly:get-mus-property music 'origin))
507       )
509     (if (ly:input-location? ip)
510         (ly:input-message ip msg)
511         (ly:warn msg))
512   ))
513   
514 (define (check-start-chords music)
515   "Check music expression for a Simultaneous_music containing notes\n(ie. Request_chords), without context specification. Called  from parser."
516   
517      (let*
518        ((es (ly:get-mus-property music 'elements))
519         (e (ly:get-mus-property music 'element))
520         (name (ly:music-name music)) 
521         )
523        (cond 
524          ((equal? name "Context_specced_music") #t)
525          ((equal? name "Simultaneous_music")
527           (if (has-request-chord es)
528               (ly:music-message music "Starting score with a chord.\nPlease insert an explicit \\context before chord")
529               (map check-start-chords es)))
530          
531          ((equal? name "Sequential_music")
532            (if (pair? es)
533                (check-start-chords (car es))))
534           (else (if (ly:music? e) (check-start-chords e )))
535        
536        ))
537      music
538      )
540 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
541 ;; switch it on here, so parsing and init isn't checked (too slow!)
543 ;; automatic music transformations.
545 (define (switch-on-debugging m)
546   (set-debug-cell-accesses! 15000)
547   m
548   )
550 (define-public toplevel-music-functions
551   (list check-start-chords
552         voicify-music
553         (lambda (x) (music-map glue-mm-rest-texts x))
554 ; switch-on-debugging
555         ))