Add string ensemble score structure
[orchestrallily.git] / orchestrallily.ily
blob74c3c08da6150a09ef4f7a362cd90019cb322bef
1 \version "2.13.17"
3 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
4 % OrchestralLily
5 % ==============
6 % Desciption:  Lilypond package to make writing large orchestral scores easier.
7 % Documentation: http://wiki.kainhofer.com/lilypond/orchestrallily
8 % Version: 0.02, 2008-03-06
9 % Author: Reinhold Kainhofer, reinhold@kainhofer.com
10 % Copyright: (C) 2008 by Reinhold Kainhofer
11 % License: Dual-licensed under either:
12 %      -) GPL v3.0, http://www.gnu.org/licenses/gpl.html
13 %      -) Creative Commons BY-NC 3.0, http://creativecommons.org/licenses/by-nc/3.0/at/
15 % Version History:
16 % 0.01 (2008-03-02): Initial Version
17 % 0.02 (2008-03-06): Added basic MIDI support (*MidiInstrument and \setCreateMIDI)
18 % 0.03 (2008-07-xx): General staff/voice types, title pages, etc.
19 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
21 #(use-modules (ice-9 match))
24 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
25 % GLOBAL OPTIONS
26 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
28 % Use relative include pathes!
29 #(ly:set-option 'relative-includes #t)
32 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
33 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
34 %%%%%   SCORE STRUCTURE AND AUTOMATIC GENERATION
35 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
36 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
41 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
42 % Helper functions
43 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
45 % Helper function to filter all non-null entries
46 #(define (not-null? x) (not (null? x)))
48 % Helper function to extract a given variable, built from [Piece][Instrument]Identifier
49 #(define (namedPieceInstrObject piece instr name)
50   (let* (
51          (fullname  (string->symbol (string-append piece instr name)))
52          (instrname (string->symbol (string-append instr name)))
53          (piecename (string->symbol (string-append piece name)))
54          (fallback  (string->symbol name))
55         )
56     (cond
57       ((defined? fullname) (primitive-eval fullname))
58       ((defined? instrname) (primitive-eval instrname))
59       ((defined? piecename) (primitive-eval piecename))
60       ((defined? fallback) (primitive-eval fallback))
61       (else '())
62     )
63   )
66 %% Print text as a justified paragraph, taken from the lilypond Notation Reference
67 #(define-markup-list-command (paragraph layout props args) (markup-list?)
68    (let ((indent (chain-assoc-get 'par-indent props 2)))
69      (interpret-markup-list layout props
70        (make-justified-lines-markup-list (cons (make-hspace-markup indent)
71                                                args)))))
73 conditionalBreak = #(define-music-function (parser location) ()
74    #{ \tag #'instrumental-score \pageBreak #}
77 #(define (oly:piece-title-markup title) (markup #:column (#:line (#:fontsize #'3 #:bold title))) )
79 #(define-markup-command (piece-title layout props title) (markup?)
80      (interpret-markup layout props (oly:piece-title-markup title))
83 #(define (oly:generate_object_name piece instr obj )
84   (if (and (string? piece) (string? instr) (string? obj))
85     (string-append piece instr obj)
86     #f
87   )
89 #(define (oly:generate_staff_name piece instr) (oly:generate_object_name piece instr "St"))
91 #(define (set-context-property context property value)
92   (set! (ly:music-property context property) value)
96 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
97 % Score structure and voice types
98 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
100 #(define oly:LiedScoreStructure '(
101   ("SoloScore" "SimultaneousMusic" ("Singstimme"))
102   ("Pfe" "PianoStaff" ("PfeI" "PfeII"))
103   ;("PfeI" "ParallelVoicesStaff" ("OIa" "OIb"))
104   ;("PfeII" "ParallelVoicesStaff" ("OIIa" "OIIb"))
105   ("FullScore" "SimultaneousMusic" ("Singstimme" "Pfe"))
106   ("VocalScore" "SimultaneousMusic" ("Singstimme" "Pfe"))
109 #(define oly:StringEnsembleScoreStructure '(
110   ("FullScore" "StaffGroup" ("VI" "VII" "Va" "Vc" "Cb" "VcB"))
113 #(define oly:fullOrchestraScoreStructure '(
114 ; Part-combined staves for full score
115   ("Fl" "PartCombinedStaff" ("FlI" "FlII"))
116   ("Ob" "PartCombinedStaff" ("ObI" "ObII"))
117   ("Cl" "PartCombinedStaff" ("ClI" "ClII"))
118   ("Fag" "PartCombinedStaff" ("FagI" "FagII"))
119   ("Wd" "StaffGroup" ("Fl" "Ob" "Cl" "Fag" "CFag"))
121   ("Cor" "PartCombinedStaff" ("CorI" "CorII"))
122   ("Tbe" "PartCombinedStaff" ("TbeI" "TbeII"))
123   ("Clni" "PartCombinedStaff" ("ClnoI" "ClnoII"))
124   ("Trb" "PartCombinedStaff" ("TrbI" "TrbII"))
125   ("Br" "StaffGroup" ("Cor" "Tbe" "Clni" "Trb" "Tba"))
127 ; long score; no part-combined staves, but GrandStaves instead
128   ("FlLong" "GrandStaff" ("FlI" "FlII"))
129   ("ObLong" "GrandStaff" ("ObI" "ObII"))
130   ("ClLong" "GrandStaff" ("ClI" "ClII"))
131   ("FagLong" "GrandStaff" ("FagI" "FagII"))
132   ("WdLong" "StaffGroup" ("FlLong" "ObLong" "ClLong" "FagLong" "CFag"))
134   ("CorLong" "GrandStaff" ("CorI" "CorII"))
135   ("TbeLong" "GrandStaff" ("TbeI" "TbeII"))
136   ("ClniLong" "GrandStaff" ("ClnoI" "ClnoII" "ClnoIII"))
137   ("TrbLong" "GrandStaff" ("TrbI" "TrbII" "TrbIII"))
138   ("BrLong" "StaffGroup" ("CorLong" "TbeLong" "ClniLong" "TrbLong" "Tba"))
140 ; Percussion
141   ("Perc" "StaffGroup" ("Tim"))
143 ; Strings, they are the same in long and short full score
144   ("VV" "GrandStaff" ("VI" "VII"))
145   ("Str" "StaffGroup" ("VV" "Va"))
146   ("VceB" "StaffGroup" ("Vc" "Cb" "VcB"))
147   ("FullStr" "StaffGroup" ("VV" "Va" "Vc" "Cb" "VcB"))
149 ; Choral score
150   ("Solo" "SimultaneousMusic" ("SSolo" "ASolo" "TSolo" "BSolo"))
151   ("Ch" "ChoirStaff" ("S" "A" "T" "B"))
152   ("ChoralScore" "SimultaneousMusic" ("Ch"))
153   ("SoloScore" "SimultaneousMusic" ("Solo"))
154   ("SoloChoirScore" "SimultaneousMusic" ("Solo" "Ch"))
156 ; Organ score (inkl. Figured bass)
157   ("BCFb" "FiguredBass" ())
158   ("FiguredBass" "FiguredBass" ())
159   ;("Organ" "SimultaneousMusic" ("BCFb" "O"))
160   ("Continuo" "ParallelVoicesStaff" ("BCFb" "BC" "FiguredBass"))
161   ("RealizedContinuo" "PianoStaff" ("BCRealization" "Continuo"))
163   ("P" "PianoStaff" ("PI" "PII"))
164   ("O" "PianoStaff" ("OI" "OII"))
165   ("OI" "ParallelVoicesStaff" ("OIa" "OIb"))
166   ("OII" "ParallelVoicesStaff" ("OIIa" "OIIb"))
168   ;("Organ" "SimultaneousMusic" ("OGroup" "RealizedContinuo"))
169   ;("BassGroup" "ParallelVoicesStaff" ("Organ" "O" "BC" "VceB"))
170   ("BassGroup" "StaffGroup" ("O" "RealizedContinuo" "Vc" "Cb" "VcB"))
172 ; Full Scores
173   ("FullScore" "SimultaneousMusic" ("Wd" "Br" "Perc" "Str" "SoloChoirScore" "BassGroup"))
174   ("LongScore" "SimultaneousMusic" ("WdLong" "BrLong" "Perc" "Str" "SoloChoirScore" "BassGroup"))
175   ("OriginalScore" "SimultaneousMusic" ("BrLong" "WdLong" "Perc" "Str" "SoloChoirScore" "BassGroup"))
177 ; Piano reduction
178   ;("Piano" "SimultaneousMusic" ("Organ"))
179   ("OrganScore" "SimultaneousMusic" ("ChoralScore" "O"))
180   ("VocalScore" "SimultaneousMusic" ("ChoralScore" "P"))
181   ("Particell"  "SimultaneousMusic" ("ChoralScore" "BassGroup"))
183 ; Full scores: Orchestral score and long score including organ
184   ("ChStrQ" "SimultaneousMusic" ("Str" "Ch" "VceB"))
186 #(define oly:orchestral_score_structure oly:fullOrchestraScoreStructure)
188 #(define (oly:set_score_structure struct)
189   (if (list? struct)
190     (set! oly:orchestral_score_structure struct)
191     (ly:warning (_ "oly:set_score_structure needs an association list as argument!"))
192   )
195 #(define (oly:modify_score_structure entry)
196   (if (list? entry)
197     (set! oly:orchestral_score_structure (assoc-set! oly:orchestral_score_structure  (car entry) (cdr entry)))
198     (ly:warning (_ "oly:modify_score_structure expects a list (\"key\" \"type\" '(children)) as argument!"))))
200 #(define (oly:remove_from_score_structure entry)
201   (if (list? entry)
202     (map oly:remove_from_score_structure entry)
203     (set! oly:orchestral_score_structure (assoc-remove! oly:orchestral_score_structure  entry))))
205 orchestralScoreStructure = #(define-music-function (parser location structure) (list?)
206   (oly:set_score_structure structure)
207   (make-music 'Music 'void #t)
210 #(define oly:voice_types '())
212 #(define (oly:set_voice_types types)
213   (if (list? types)
214     (set! oly:voice_types types)
215     (ly:warning (_ "oly:set_voice_types needs an association list as argument!"))
216   )
219 orchestralVoiceTypes = #(define-music-function (parser location types) (list?)
220   (oly:set_voice_types types)
221   (make-music 'Music 'void #t)
225 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
226 % Automatic staff and group generation
227 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
229 % Retrieve all music definitions for the given
230 #(define (oly:get_music_object piece instrument)
231   (namedPieceInstrObject piece instrument "Music")
233 #(define (oly:get_music_objects piece instruments)
234   (filter not-null? (map (lambda (i) (oly:get_music_object piece i)) instruments))
237 % Given a property name and the extensions, either generate the pair to set
238 % the property or an empty list, if no pre-defined variable could be found
239 #(define (oly:generate_property_pair prop piece instr type)
240   (let* ((val (namedPieceInstrObject piece instr type)))
241     (if (not-null? val) (list 'assign prop val) '() )
242   )
245 #(define (oly:staff_type type)
246   (cond
247     ((string? type) (string->symbol type))
248     ((symbol? type) type)
249     (else 'Staff)
250   )
253 #(define (oly:extractPitch music)
254   (let* (
255          (elems  (if (ly:music? music) (ly:music-property music 'elements)))
256          (note   (if (pair? elems) (car elems)))
257          (pitch  (if (ly:music? note) (ly:music-property note 'pitch)))
258         )
259     (if (and (not-null? music) (not (ly:pitch? pitch)))
260       (ly:warning "Unable to interpret as a pitch!")
261     )
262     pitch
263   )
266 #(define (oly:extractTranspositionPitch piece name)
267   (let* (
268          (trpFromPitch (oly:extractPitch (namedPieceInstrObject piece name "TransposeFrom")))
269          (trpToPitch   (oly:extractPitch (namedPieceInstrObject piece name "TransposeTo")))
270         )
271     (if (ly:pitch? trpFromPitch)
272       (if (ly:pitch? trpToPitch)
273         ; Both pitches
274         (ly:pitch-diff trpFromPitch trpToPitch)
275         (ly:pitch-diff trpFromPitch (ly:make-pitch 0 0 0))
276       )
277       (if (ly:pitch? trpToPitch)
278         (ly:pitch-diff (ly:make-pitch 0 0 0) trpToPitch)
279         #f
280       )
281     )
282   )
286 %%=====================================================================
287 %% Extract context modifications for given objects
288 %%---------------------------------------------------------------------
291 % TODO: join these property extractors to avoid code duplication
293 % Generate the properties for the lyrics for piece and instr.
294 % Also check whether we have a modifications object to fech mods from.
295 % return a (possibly empty) list of all assignments.
296 #(define (oly:lyrics_handler_properties piece name lyricsid)
297   (let* (
298          (mods (namedPieceInstrObject piece name (string-append lyricsid "Modifications")))
299          (mod-list (if (not-null? mods) (ly:get-context-mods mods) '()))
300          (mapping '(
301              ;(instrumentName . "InstrumentName")
302              ;(shortInstrumentName . "ShortInstrumentName")
303              ;(midiInstrument . "MidiInstrument")
304             ))
305          (assignments (map
306              (lambda (pr)
307                  (oly:generate_property_pair (car pr) piece name (cdr pr))
308              )
309              mapping))
310          (olyprops (filter not-null? assignments))
311          (props (append mod-list olyprops))
312         )
313     props
314   )
317 % Generate the properties for the voice for piece and instr.
318 % Also check whether we have a modifications object to fech mods from.
319 % return a (possibly empty) list of all assignments.
320 #(define (oly:voice_handler_properties piece name)
321   (let* (
322          (mods (namedPieceInstrObject piece name "VoiceModifications"))
323          (mod-list (if (not-null? mods) (ly:get-context-mods mods) '()))
324          (mapping '(
325              ;(instrumentName . "InstrumentName")
326              ;(shortInstrumentName . "ShortInstrumentName")
327              ;(midiInstrument . "MidiInstrument")
328             ))
329          (assignments (map
330              (lambda (pr)
331                  (oly:generate_property_pair (car pr) piece name (cdr pr))
332              )
333              mapping))
334          (olyprops (filter not-null? assignments))
335          (props (append mod-list olyprops))
336         )
337     props
338   )
341 % Generate the properties for the staff for piece and instr. Typically, these
342 % are the instrument name and the short instrument name (if defined).
343 % Also check whether we have a modifications object to fech mods from.
344 % return a (possibly empty) list of all assignments.
345 #(define (oly:staff_handler_properties piece instr)
346   (let* (
347          (mods (namedPieceInstrObject piece instr "StaffModifications"))
348          (mod-list (if (not-null? mods) (ly:get-context-mods mods) '()))
349          (mapping '(
350               (instrumentName . "InstrumentName")
351               (shortInstrumentName . "ShortInstrumentName")
352               (midiInstrument . "MidiInstrument")
353             ))
354          (assignments (map
355              (lambda (pr)
356                  (oly:generate_property_pair (car pr) piece instr (cdr pr))
357              )
358              mapping))
359          (olyprops (filter not-null? assignments))
360          (props (append mod-list olyprops))
361         )
362     props
363   )
369 %%=====================================================================
370 %% Extract contents for voices
371 %%---------------------------------------------------------------------
373 #(define (oly:musiccontent_for_voice parser piece name music additional)
374   (let* ((musiccontent additional))
376     ; Append the settings, key and clef (if defined)
377     (map
378       (lambda (type)
379         (let* ((object (namedPieceInstrObject piece name type)))
380           (if (ly:music? object)
381             (set! musiccontent (append musiccontent (list (ly:music-deep-copy object))))
382             (if (not-null? object) (ly:warning (_ "Wrong type (no ly:music) for ~S for instrument ~S in piece ~S") type name piece))
383           )
384         )
385       )
386       ; TODO: Does the "Tempo" work here???
387       '("Settings" "Key" "Clef" "TimeSignature" "ExtraSettings";"Tempo"
388       )
389     )
391     (if (ly:music? music)
392       (begin
393         (set! musiccontent (make-simultaneous-music (append musiccontent (list music))))
394         ;(ly:message "Generating staff for ~a" name)
395         (let* ((trpPitch (oly:extractTranspositionPitch piece name)))
396           (if (ly:pitch? trpPitch)
397             (set! musiccontent (ly:music-transpose musiccontent trpPitch))
398           )
399         )
400         musiccontent
401       )
402       ; For empty music, return empty
403       '()
404     )
405   )
410 %%=====================================================================
411 %% create Lyrics
412 %%---------------------------------------------------------------------
415 #(define (oly:lyrics_create_single_context parser piece name voicename lyricsid)
416   ; If we have lyrics, create a lyrics context containing LyricCombineMusic
417   ; and add that as second element to the staff's elements list...
418   ; Also add possibly configured LyricsModifications
419   (let* ((id (string-append "Lyrics" lyricsid))
420          (lyricsmods (oly:lyrics_handler_properties piece name id))
421          (lyrics (namedPieceInstrObject piece name id))
422          (ctx (if (ly:music? lyrics)
423                   (context-spec-music (make-music 'LyricCombineMusic
424                                                   'element lyrics
425                                                   'associated-context voicename)
426                                       'Lyrics
427                                       (oly:generate_object_name piece name id))
428                   '())))
429     (if (and (not-null? lyricsmods) (not-null? ctx))
430       (set! (ly:music-property ctx 'property-operations) lyricsmods)
431     )
432     ctx
433   )
436 #(define (oly:lyrics_create_contexts parser piece name voicename)
437   (filter not-null?
438     (map (lambda (str)
439                  (oly:lyrics_create_single_context parser piece name voicename str))
440          (list "" "I" "II" "III"  "IV" "V" "VI"))))
443 %%=====================================================================
444 %% Voice handling
445 %%---------------------------------------------------------------------
448 #(define (oly:voice_handler_internal parser piece name type music)
449   (if (ly:music? music)
450     (let* (
451            (voicename    (oly:generate_object_name piece name "Voice" ))
452            (lyrics       (oly:lyrics_create_contexts parser piece name voicename))
453            (additional   (if (not-null? lyrics) (list dynamicUp) '()))
454            (musiccontent (oly:musiccontent_for_voice parser piece name music additional))
455            (voicetype    (oly:staff_type type))
456            (voice        (context-spec-music musiccontent voicetype voicename))
457            (voiceprops   (oly:voice_handler_properties piece name))
458           )
459       (if (not-null? voiceprops)
460         (set! (ly:music-property voice 'property-operations) voiceprops)
461       )
462       (cons voice lyrics)
463     )
464     ; For empty music, return empty
465     '()
466   )
469 #(define (oly:voice_handler parser piece name type)
470   (oly:voice_handler_internal parser piece name type (oly:get_music_object piece name)))
473 %%=====================================================================
474 %% Staff/Group handling
475 %%---------------------------------------------------------------------
478 #(define (oly:staff_handler_internal parser piece name type voices)
479   (if (not-null? voices)
480     (let* (
481            (staffname  (oly:generate_staff_name piece name))
482            (stafftype  (oly:staff_type type))
483            (staff      (make-simultaneous-music voices))
484            (propops    (oly:staff_handler_properties piece name))
485           )
486       (case stafftype
487         ((SimultaneousMusic ParallelMusic) #f)
488         (else (set! staff (context-spec-music staff stafftype staffname)))
489       )
490       (if (not-null? propops)
491         (set! (ly:music-property staff 'property-operations) propops)
492       )
493       staff
494     )
495     ; For empty music, return empty
496     '()
497   )
500 #(define (oly:staff_handler parser piece name type children)
501   (let* ((c (if (not-null? children) children (list name)))
502          (voices (apply append (map (lambda (v) (oly:create_voice parser piece v)) c)) )
503         )
504     (if (not-null? voices)
505       (oly:staff_handler_internal parser piece name type voices)
506       '()
507     )
508   )
511 #(define (oly:devnull_handler parser piece name type children)
512   (oly:voice_handler parser piece name type)
515 #(define (oly:parallel_voices_staff_handler parser piece name type children)
516   (let* (
517          (voices (map (lambda (i) (oly:create_voice parser piece i)) children))
518          ; get the list of non-empty voices and flatten it!
519          (nonemptyvoices (apply append (filter not-null? voices)))
520         )
521     (if (not-null? nonemptyvoices)
522       (oly:staff_handler_internal parser piece name "Staff" nonemptyvoices)
523       '()
524     )
525   )
528 #(define (oly:remove-with-tag tag music)
529   (if (ly:music? music)
530       (music-filter
531         (lambda (m)
532           (let* ((tags (ly:music-property m 'tags))
533                  (res (memq tag tags)))
534             (not res)))
535         music)
536       music))
538 % Remove all music tagged a not-part-combine
539 #(define (oly:remove-non-part-combine-events music)
540   (oly:remove-with-tag 'non-partcombine music))
542 #(define (oly:part_combined_staff_handler parser piece name type children)
543   (let* ((rawmusic (map (lambda (c) (oly:musiccontent_for_voice parser piece name (oly:get_music_object piece c) '())) children))
544          (filteredmusic (map (lambda (m) (oly:remove-non-part-combine-events m)) rawmusic))
545          (music (filter not-null? filteredmusic)))
546   (cond
547       ((and (pair? music) (ly:music? (car music)) (not-null? (cdr music)) (ly:music? (cadr music)))
548           ;(ly:message "Part-combine with two music expressions")
549           (oly:staff_handler_internal parser piece name "Staff" (list (make-part-combine-music parser music))))
550       ((null? music)
551           ;;(ly:warning "Part-combine without any music expressions")
552           '())
553       ; exactly one is a music expression, simply use that by joining
554       ((list? music)
555           ;;(ly:message "Part-combine with only one music expressions")
556           (oly:staff_handler_internal parser piece name "Staff" (list (apply append music))))
557       (else
558           ;(ly:message "make_part_combined_staff: ~S ~S ~a" piece instr instruments)
559           '() )
560     )
561   )
564 % Figured bass is a special case, as it can be voice- or staff-type. When
565 % given as a staff type, simply call the voice handler, instead
567 #(define (oly:figured_bass_staff_handler parser piece name type children)
568   (let* ((c (if (not-null? children) children (list name)))
569          (voice  (oly:voice_handler parser piece (car c) type)))
570     (if (pair? voice) (car voice) ())
571   )
574 #(define (flatten lst)
575   (define (f remaining result)
576     (cond
577       ((null? remaining) result)
578       ((pair? (car remaining)) (f (cdr remaining) (f (car remaining) result)))
579       (else (f (cdr remaining) (cons (car remaining) result)))))
580   (reverse! (f lst '())))
582 #(define (oly:staff_group_handler parser piece name type children)
583   (let* (
584          (staves (flatten (map (lambda (i) (oly:create_staff_or_group parser piece i)) children)))
585          (nonemptystaves (filter not-null? staves))
586         )
587     (if (not-null? nonemptystaves)
588       (let* (
589              (musicexpr (if (= 1 (length nonemptystaves))
590                           (car nonemptystaves)
591                           (make-simultaneous-music nonemptystaves)))
592              (groupname (oly:generate_staff_name piece name))
593              (grouptype (oly:staff_type type))
594              (group     musicexpr)
595              (propops   (oly:staff_handler_properties piece name))
596             )
597         (case grouptype
598           ((SimultaneousMusic ParallelMusic) #f)
599           (else (set! group (context-spec-music group grouptype groupname)))
600         )
601         (if (pair? propops)
602           (set! (ly:music-property group 'property-operations) propops))
603         group
604       )
605       ; Return empty list if no staves are generated
606       '()
607     )
608   )
611 #(define (oly:create_voice parser piece name)
612   (let* ( (voice (namedPieceInstrObject piece name "Voice"))
613           (type (assoc-ref oly:voice_types name)) )
614     (if (not-null? voice)
615       ; Explicit voice variable, use that
616       voice
618       (if (not type)
619         ; No entry in structure found => simple voice
620         (oly:voice_handler parser piece name "Voice")
621         ; Entry found in structure => use the handler for the given type
622         (let* (
623                (voicetype (car type))
624                (handler (assoc-ref oly:voice_handlers voicetype))
625               )
626           (if handler
627             ((primitive-eval handler) parser piece name voicetype)
628             (begin
629               (ly:warning "No handler found for voice type ~a, using default voice handler" voicetype)
630               (oly:voice_handler parser piece name voicetype)
631             )
632           )
633         )
634       )
635     )
636   )
639 #(define (oly:create_staff_or_group parser piece name)
640   (let* ( (staff (namedPieceInstrObject piece name "Staff"))
641           (type_from_structure (assoc-ref oly:orchestral_score_structure name)) )
642     ;(if (not-null? staff)
643     ;  (ly:message "Found staff variable for instrument ~a in piece ~a"  instr piece)
644     ;  (ly:message "Staff variable for instrument ~a in piece ~a NOT FOUND"  instr piece)
645     ;)
646     (if (not-null? staff)
647       ; Explicit staff variable, use that
648       staff
650       (if (not (list? type_from_structure))
651         ; No entry in structure found => simple staff
652         (oly:staff_handler parser piece name "Staff" '())
654         ; Entry found in structure => use the handler for the given type
655         (let* ((type (car type_from_structure))
656                (handler (assoc-ref oly:staff_handlers type))
657                (children (cadr type_from_structure))
658               )
659           (if handler
660             ((primitive-eval handler) parser piece name type children)
661             (begin
662               (ly:warning "No handler found for staff type ~a, using default staff handler" type)
663               (oly:staff_handler parser piece name type children)
664             )
665           )
666         )
667       )
668     )
669   )
672 #(define (oly:dynamics_handler parser piece name type children)
673   (oly:voice_handler parser piece name type)
677 %%=====================================================================
678 %% Handler definitions
679 %%---------------------------------------------------------------------
681 #(define oly:staff_handlers
682   (list
683     ; staff group types
684     '("GrandStaff" . oly:staff_group_handler )
685     '("PianoStaff" . oly:staff_group_handler )
686     '("ChoirStaff" . oly:staff_group_handler )
687     '("StaffGroup" . oly:staff_group_handler )
688     '("ParallelMusic" . oly:staff_group_handler )
689     '("SimultaneousMusic" . oly:staff_group_handler )
690     ; staff types
691     '("Staff" . oly:staff_handler )
692     '("DrumStaff" . oly:staff_handler )
693     '("RhythmicStaff" . oly:staff_handler )
694     '("TabStaff" . oly:staff_handler )
695     '("GregorianTranscriptionStaff" . oly:staff_handler )
696     '("MensuralStaff" . oly:staff_handler )
697     '("VaticanaStaff" . oly:staff_handler )
698     ; staves with multiple voices
699     '("PartCombinedStaff" . oly:part_combined_staff_handler )
700     '("ParallelVoicesStaff" . oly:parallel_voices_staff_handler )
701     ; special cases: Figured bass can be staff or voice type!
702     '("FiguredBass" . oly:figured_bass_staff_handler )
703     ; Devnull is like a staff, only that it doesn't craete output
704     '("Devnull" . oly:devnull_handler )
705     '("Dynamics" . oly:dynamics_handler )
706   )
709 #(define oly:voice_handlers
710   (list
711     ; voice types
712     '("Voice" . oly:voice_handler )
713     '("CueVoice" . oly:voice_handler )
714     '("DrumVoice" . oly:voice_handler )
715     '("FiguredBass" . oly:voice_handler )
716     '("GregorianTranscriptionVoice" . oly:voice_handler )
717     '("NoteNames" . oly:voice_handler )
718     '("TabVoice" . oly:voice_handler )
719     '("VaticanaVoice" . oly:voice_handler )
720   )
724 #(define (oly:register_staff_type_handler type func)
725 ;  (ly:message "Registering staff handler ~a for type ~a" func type)
726   (set! oly:staff_handlers (assoc-set! oly:staff_handlers type func))
729 #(define (oly:register_voice_type_handler type func)
730 ;  (ly:message "Registering voice type handler ~a for type ~a" func type)
731   (set! oly:voice_handlers (assoc-set! oly:voice_handlers type func))
734 % handlers for deprecated API
735 #(oly:register_staff_type_handler 'StaffGroup 'oly:staff_group_handler)
736 #(oly:register_staff_type_handler 'GrandStaff 'oly:staff_group_handler)
737 #(oly:register_staff_type_handler 'PianoStaff 'oly:staff_group_handler)
738 #(oly:register_staff_type_handler 'ChoirStaff 'oly:staff_group_handler)
739 #(oly:register_staff_type_handler 'Staff 'oly:staff_handler )
740 #(oly:register_staff_type_handler 'ParallelMusic 'oly:staff_group_handler)
741 #(oly:register_staff_type_handler 'SimultaneousMusic 'oly:staff_group_handler)
742 #(oly:register_staff_type_handler #t 'oly:part_combined_staff_handler )
743 #(oly:register_staff_type_handler #f 'oly:parallel_voices_staff_handler )
747 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
748 % Automatic score generation
749 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
751 #(define oly:score_handler add-score)
752 #(define oly:music_handler add-music)
753 #(define oly:text_handler add-text)
756 % TODO: deprecate
757 setUseBook = #(define-music-function (parser location usebook) (boolean?)
758   (ly:warning "\\setUseBook has been deprecated! Books are now automatically handled without any hacks")
759   (make-music 'Music 'void #t)
763 % Two functions to handle midi-blocks: Either don't set one, or set an empty
764 % one so that MIDI is generated
765 #(define (oly:set_no_midi_block score) '())
766 #(define (oly:set_midi_block score)
767   (let* ((midiblock (if (defined? '$defaultmidi)
768                         (ly:output-def-clone $defaultmidi)
769                         (ly:make-output-def))))
770     (ly:output-def-set-variable! midiblock 'is-midi #t)
771     (ly:score-add-output-def! score midiblock)
772   )
775 % \setCreateMidi ##t/##f sets a flag to determine wheter MIDI output should
776 % be generated
777 #(define oly:apply_score_midi oly:set_no_midi_block)
778 setCreateMIDI = #(define-music-function (parser location createmidi) (boolean?)
779   (if createmidi
780     (set! oly:apply_score_midi oly:set_midi_block)
781     (set! oly:apply_score_midi oly:set_no_midi_block)
782   )
783   (make-music 'Music 'void #t)
787 % Two functions to handle layout-blocks: Either don't set one, or set an empty
788 % one so that a PDF is generated
789 #(define (oly:set_no_layout_block score) '())
790 #(define (oly:set_layout_block score)
791   (let* ((layoutblock (if (defined? '$defaultlayout)
792                         (ly:output-def-clone $defaultlayout)
793                         (ly:make-output-def))))
794     (ly:output-def-set-variable! layoutblock 'is-layout #t)
795     (ly:score-add-output-def! score layoutblock)
796   )
799 % \setCreatePDF ##t/##f sets a flag to determine wheter PDF output should
800 % be generated
801 #(define oly:apply_score_layout oly:set_no_layout_block)
802 setCreatePDF = #(define-music-function (parser location createlayout) (boolean?)
803   (if createlayout
804     (set! oly:apply_score_layout oly:set_layout_block)
805     (set! oly:apply_score_layout oly:set_no_layout_block)
806   )
807   (make-music 'Music 'void #t)
811 % Set the piece title in a new header block.
812 #(define (oly:set_piece_header score piecename)
813   (if (not-null? piecename)
814     (let* ((header (make-module)))
815       (module-define! header 'piece piecename)
816       (ly:score-set-header! score header)
817     )
818   )
822 % post-filter functions. By default, no filtering is done. However,
823 % for the *NoCues* function, the cue notes should be killed
824 keepcuefilter = #(define-music-function (parser location music) (ly:music?)
825   ((ly:music-function-extract removeWithTag) parser location 'non-cued music))
826 removecuefilter = #(define-music-function (parser location music) (ly:music?)
827   ((ly:music-function-extract removeWithTag) parser location 'cued ((ly:music-function-extract killCues) parser location music)))
830 #(define (oly:create-toc-file layout pages)
831   (let* ((label-table (ly:output-def-lookup layout 'label-page-table))
832          ;; The page numbers are pages counts in the pdf file, not visible page number!
833          ;; So we have to offset them if the first page is not page #1
834          (first-page-offset (1- (ly:output-def-lookup layout 'first-page-number))))
835     (if (not (null? label-table))
836       (let* ((format-line (lambda (toc-item)
837              (let* ((label (car toc-item))
838                     (text  (caddr toc-item))
839                     (label-page (and (list? label-table)
840                                      (assoc label label-table)))
841                     (page (and label-page (cdr label-page))))
842                (format #f "~a, section, 1, {~a}, ~a" (- page first-page-offset) text label))))
843              (formatted-toc-items (map format-line (toc-items)))
844              (whole-string (string-join formatted-toc-items ",\n"))
845              (output-name (ly:parser-output-name parser))
846              (outfilename (format "~a.toc" output-name))
847              (outfile (open-output-file outfilename)))
848         (if (output-port? outfile)
849             (display whole-string outfile)
850             (ly:warning (_ "Unable to open output file ~a for the TOC information") outfilename))
851         (close-output-port outfile)))))
854 #(define-public (oly:add-toc-item parser markup-symbol text)
855   (oly:music_handler parser (add-toc-item! markup-symbol text)))
858 #(define (oly:add-score parser score piecename)
859   (if (not-null? piecename)
860     (oly:add-toc-item parser 'tocItemMarkup piecename))
861   (oly:score_handler parser score)
863 % The helper function to build a score.
864 #(define (oly:createScoreHelper parser location piece children func)
865   (let* (
866          (staves    (oly:staff_group_handler parser piece "" "SimultaneousMusic" children))
867          (music     (if (not-null? staves)
868                         ((ly:music-function-extract func) parser location staves)
869                         '()
870                     ))
871          (score     '())
872          (piecename (namedPieceInstrObject piece (car children) "PieceName"))
873          (piecenametacet (namedPieceInstrObject piece (car children) "PieceNameTacet"))
874          (header    '())
875         )
876     (if (null? music)
877       ; No staves, print tacet
878       (begin
879         (if (not-null? piecenametacet) (set! piecename piecenametacet))
880         (if (not-null? piecename)
881           (oly:add-score parser (list (oly:piece-title-markup piecename)) piecename)
882           (ly:warning (_ "No music and no score title found for part ~a and instrument ~a") piece children)
883         )
884       )
885       ; we have staves, apply the piecename to the score and add layout/midi blocks if needed
886       (begin
887         (set! score (scorify-music music parser))
888         (oly:set_piece_header score piecename)
889         (oly:apply_score_midi score)
890         (oly:apply_score_layout score)
891         ; Schedule the score for typesetting
892         (oly:add-score parser score piecename)
893       )
894     )
895   )
896   ; This is a void function, the score has been schedulled for typesetting already
897   (make-music 'Music 'void #t)
900 createVoice = #(define-music-function (parser location piece name) (string? string?)
901   (let* ((vc (oly:create_voice parser piece name)))
902     (make-music 'SimultaneousMusic
903                 'elements vc)))
905 createStaff = #(define-music-function (parser location piece name) (string? string?)
906   (oly:create_staff_or_group parser piece name))
907 createStaffForContents = #(define-music-function (parser location piece name contents) (string? string? ly:music?)
908   (let* ((tstruct (assoc-ref oly:orchestral_score_structure name))
909          (type (if (list? tstruct) (car tstruct) "Staff")))
910     (oly:staff_handler_internal parser piece name type (list contents))))
913 createScore = #(define-music-function (parser location piece children) (string? list?)
914   (oly:createScoreHelper parser location piece children keepcuefilter)
916 createNoCuesScore = #(define-music-function (parser location piece children) (string? list?)
917   (oly:createScoreHelper parser location piece children removecuefilter)
920 createHeadline = #(define-music-function (parser location headline) (string?)
921   (oly:add-toc-item parser 'tocItemMarkup headline)
922   (oly:score_handler parser (list (oly:piece-title-markup headline)))
923   (make-music 'Music 'void #t)
928 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
929 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
930 %%%%%   CUE NOTES
931 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
932 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
934 newInstrument = #(define-music-function (parser location instr) (string?)
936   \set Voice.instrumentCueName = #$(string-join (list "+" instr))
939 cueText = #(define-music-function (parser location instr) (string?)
941   \set Voice.instrumentCueName = $instr
944 cueMarkup = #(define-music-function (parser location instr) (markup?)
946   \set Voice.instrumentCueName = $instr
950 clearCueText = #(define-music-function (parser location) ()
952   \unset Voice.instrumentCueName
956 insertCueText = #(define-music-function (parser location instr) (string?)
957   (if (string-null? instr)
958     #{ \tag #'cued \clearCueText #}
959     #{ \tag #'cued \cueText #$instr #}
962 % generate a cue music section with instrument names
963 % Parameters: \namedCueDuring NameOfQuote CueDirection CueInstrument OriginalInstrument music
964 %                 -) NameOfQuote CueDirection music are the parameters for \cueDuring
965 %                 -) CueInstrument and OriginalInstrument are the displayed instrument names
966 % typical call:
967 % \namedCueDuring #"vIQuote" #UP #"V.I" #"Sop." { R1*3 }
968 %      This adds the notes from vIQuote (defined via \addQuote) to three measures, prints "V.I" at
969 %      the beginning of the cue notes and "Sop." at the end
970 namedCueDuring = #(define-music-function (parser location cuevoice direction instrcue instr cuemusic) (string? number? string? string? ly:music?)
972   \cueDuring #$cuevoice #$direction {
973     \insertCueText #$instrcue
974     $cuemusic
975     \insertCueText #$instr
976   }
979 namedTransposedCueDuring = #(define-music-function (parser location cuevoice direction instrcue instr trans cuemusic) (string? number? string? string? ly:music? ly:music?)
980    #{
981      \transposedCueDuring #$cuevoice #$direction $trans {
982        \insertCueText #$instrcue
983        $cuemusic
984        \insertCueText #$instr
985      }
986    #}
989 % set the cue instrument name and clef
990 setClefCue = #(define-music-function (parser location instr clef)
991                                                      (string? ly:music?)
992    #{
993      \once \override Staff.Clef #'font-size = #-3 $clef
994      \insertCueText $instr
995    #} )
997 % generate a cue music section with instrument names and clef changes
998 % Parameters: \cleffedCueDuring NameOfQuote CueDirection CueInstrument CueClef OriginalInstrument OriginalClef music
999 %                 -) NameOfQuote CueDirection music are the parameters for \cueDuring
1000 %                 -) CueInstrument and OriginalInstrument are the displayed instrument names
1001 %                 -) CueClef and OriginalClef are the clefs for the the cue notes and the clef of the containing voice
1002 % typical call:
1003 % \cleffedCueDuring #"vIQuote" #UP #"V.I" #"treble" #"Basso" #"bass" { R1*3 }
1004 %      This adds the notes from vIQuote (defined via \addQuote) to three measures, prints "V.I" at
1005 %      the beginning of the cue notes and "Basso" at the end. The clef is changed to treble at the
1006 %      beginning of the cue notes and reset to bass at the end
1007 cleffedCueDuring = #(define-music-function (parser location cuevoice direction instrcue clefcue instr clefinstr cuemusic)
1008                                                         (string? number? string? ly:music? string? ly:music? ly:music?)
1009    #{
1010      \cueDuring #$cuevoice #$direction {
1011        \tag #'cued \setClefCue #$instrcue $clefcue
1012        $cuemusic
1013        \tag #'cued \setClefCue #$instr $clefinstr
1014      }
1015    #}
1017 % generate a cue music section with instrument names and clef changes
1018 % Parameters: \namedCueDuringClef NameOfQuote CueDirection CueInstrument CueClef OriginalInstrument music
1019 %                 -) NameOfQuote CueDirection music are the parameters for \cueDuring
1020 %                 -) CueInstrument and OriginalInstrument are the displayed instrument names
1021 %                 -) CueClef is the clef for the the cue notes
1022 % typical call:
1023 % \namedCueDuringClef #"vIQuote" #UP #"V.I" #"treble" #"Basso" { R1*3 }
1024 %      This adds the notes from vIQuote (defined via \addQuote) to three measures, prints "V.I" at
1025 %      the beginning of the cue notes and "Basso" at the end. The clef is changed to treble at the
1026 %      beginning of the cue notes and reset to bass at the end
1027 namedCueDuringWithClef = #(define-music-function (parser location cuevoice direction instrcue clefcue instr cuemusic)
1028                                              (string? number? string? string? string? ly:music?)
1029    #{
1030      \cueDuringWithClef #$cuevoice #$direction #$clefcue {
1031        \insertCueText #$instrcue
1032        $cuemusic
1033        \insertCueText #$instr
1034      }
1035    #}
1040 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1041 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1042 %%%%%   DYNAMICS
1043 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1044 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1047 dynamicsX = #(define-music-function (parser location offset) (number?)
1049     \once \override DynamicText #'X-offset = $offset
1050     \once \override DynamicLineSpanner #'Y-offset = #0
1053 % Move the dynamic sign inside the staff to a fixed staff-relative position
1054 % posY (where 0 means vertically starts at the middle staff line)
1055 dynamicsAllInside = #(define-music-function (parser location offsetX posY)
1056 (number? number?)
1058   % Invalid y-extent -> hidden from skyline calculation and collisions
1059 %   \once \override DynamicLineSpanner #'Y-extent = #(cons +0 -0.01)
1060   \once \override DynamicLineSpanner #'Y-extent = $(lambda (grob)
1061     (let* ((ext (ly:axis-group-interface::height grob))
1062            (dir (ly:grob-property grob 'direction)))
1063       (if (eq? dir UP)
1064             (cons (- (cdr ext) 0.1) (cdr ext))
1065             (cons (car ext)         (+ (car ext) 0.1)))))
1066   % move by X offset and to fixed Y-position (use Y-offset of parent!)
1067   \once \override DynamicText #'X-offset = $offsetX
1068   \once \override DynamicText #'Y-offset =
1069     $(lambda (grob)
1070        (let* ((head (ly:grob-parent grob Y))
1071               (offset (ly:grob-property head 'Y-offset)))
1072          (- posY  offset (- 0.6))))
1073   \once \override DynamicLineSpanner #'Y-offset = $posY
1076 dynamicsUpInside = #(define-music-function (parser location offsetX) (number?)
1077   ((ly:music-function-extract dynamicsAllInside) parser location offsetX 1.5)
1080 dynamicsDownInside = #(define-music-function (parser location offsetX) (number?)
1081   ((ly:music-function-extract dynamicsAllInside) parser location offsetX -3.5)
1084 hairpinOffset = #(define-music-function (parser location posY) (number?)
1086   \once \override DynamicLineSpanner #'Y-offset = $posY
1087   \once \override DynamicLineSpanner #'Y-extent = #(cons +0 -0.01)
1090 #(define ((line-break-offset before after) grob)
1091   (let* ((orig (ly:grob-original grob))
1092          ; All siblings if line-broken:
1093          (siblings (if (ly:grob? orig) (ly:spanner-broken-into orig) '() )))
1094     (if (>= (length siblings) 2)
1095       ; We have been line-broken
1096       (if (eq? (car (last-pair siblings)) grob)
1097         ; Last sibling:
1098         (ly:grob-set-property! grob 'Y-offset after)
1099         ; Others get the before value:
1100         (ly:grob-set-property! grob 'Y-offset before)
1101       )
1102     )
1103   )
1106 ffz = #(make-dynamic-script "ffz")
1107 pf = #(make-dynamic-script "pf")
1108 sempp = #(make-dynamic-script (markup #:line( #:with-dimensions '(0 . 0)
1109 '(0 . 0) #:right-align #:normal-text #:italic "sempre" #:dynamic "pp")))
1110 parenf = #(make-dynamic-script (markup #:line(#:normal-text #:italic #:fontsize 2 "(" #:dynamic "f" #:normal-text #:italic #:fontsize 2 ")")))
1111 parenp = #(make-dynamic-script (markup #:line(#:normal-text #:italic #:fontsize 2 "(" #:dynamic "p" #:normal-text #:italic #:fontsize 2 ")")))
1112 pdolce = #(make-dynamic-script (markup #:line(#:dynamic "p" #:with-dimensions '(0 . 0) '(0 . 0) #:normal-text #:italic "dolce")))
1113 dolce = #(make-dynamic-script (markup #:line(#:normal-text #:italic "dolce")))
1114 sfpdolce = #(make-dynamic-script (markup #:line(#:dynamic "sfp" #:with-dimensions '(0 . 0) '(0 . 0) #:normal-text #:italic "dolce"  )))
1115 bracketf = #(make-dynamic-script (markup #:line(#:concat(#:normal-text #:fontsize 3 "[" #:dynamic "f" #:hspace 0.1 #:normal-text #:fontsize 3 "]"))))
1116 bracketmf = #(make-dynamic-script (markup #:line(#:concat(#:normal-text #:fontsize 3 "[" #:dynamic "mf" #:hspace 0.1 #:normal-text #:fontsize 3 "]"))))
1117 bracketmp = #(make-dynamic-script (markup #:line(#:concat(#:normal-text #:fontsize 2 "[" #:hspace 0.2 #:dynamic "mp" #:normal-text #:fontsize 2 "]"))))
1118 bracketp = #(make-dynamic-script (markup #:line(#:concat(#:normal-text #:fontsize 2 "[" #:hspace 0.2 #:dynamic "p" #:normal-text #:fontsize 2 "]"))))
1120 whiteoutp = #(make-dynamic-script (markup #:whiteout #:pad-markup 0.5 #:dynamic "p"))
1121 whiteoutf = #(make-dynamic-script (markup #:whiteout #:pad-markup 0.5 #:dynamic "f"))
1122 whiteoutff = #(make-dynamic-script (markup #:whiteout #:pad-markup 0.25 #:dynamic "ff"))
1125 % cresc = #(make-music 'CrescendoEvent 'span-direction START 'crescendoSpanner 'text 'crescendoText "cresc.")
1126 % endcresc =  #(make-span-event 'CrescendoEvent STOP)
1127 % dim = #(make-music 'DecrescendoEvent 'span-direction START 'decrescendoSpanner 'text 'decrescendoText "dim.")
1128 % enddim =  #(make-span-event 'DecrescendoEvent STOP)
1129 % decresc = #(make-music 'DecrescendoEvent 'span-direction START 'decrescendoSpanner 'text 'decrescendoText "decresc.")
1130 % enddecresc =  #(make-span-event 'DecrescendoEvent STOP)
1132 % setCresc = {}
1133 % setDecresc = {}
1134 % setDim = {}
1135 cresc = #(make-music 'CrescendoEvent 'span-direction START
1136                      'span-type 'text 'span-text "cresc.")
1137 dim = #(make-music 'DecrescendoEvent 'span-direction START
1138                    'span-type 'text 'span-text "dim.")
1139 decresc = #(make-music 'DecrescendoEvent 'span-direction START
1140                        'span-type 'text 'span-text "decresc.")
1142 % newOrOldClef = #(define-music-function (parser location new old ) (string? string?)
1143 %     (if (ly:get-option 'old-clefs) #{ \clef $old #} #{ \clef $new #})
1144 % )
1148 %%% Thanks to "Gilles THIBAULT" <gilles.thibault@free.fr>, there is a way
1149 %   to remove also the fermata from R1-\fermataMarkup: By filtering the music
1150 %   and removing the corresponding events.
1151 %   Documented as an LSR snippet: http://lsr.dsi.unimi.it/LSR/Item?id=372
1152 #(define (filterOneEventsMarkup event)
1153 ( let ( (eventname (ly:music-property  event 'name)) )
1154  (not
1155   (or     ;; add here event name you do NOT want
1156    (eq? eventname 'MultiMeasureTextEvent)
1157    (eq? eventname 'AbsoluteDynamicEvent)
1158    (eq? eventname 'TextScriptEvent)
1159    (eq? eventname 'ArticulationEvent)
1160    (eq? eventname 'CrescendoEvent)
1161    (eq? eventname 'DecrescendoEvent)
1162   )
1166 filterArticulations = #(define-music-function (parser location music) (ly:music?)
1167   (music-filter filterOneEventsMarkup music)
1174 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1175 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1176 %%%%%   Tempo markings
1177 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1178 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1182 rit = \markup {\italic "rit."}
1183 atempo = \markup {\italic "a tempo"}
1184 pocorit = \markup {\italic "poco rit."}
1185 ppmosso = \markup {\italic "poco più mosso"}
1186 pizz = \markup {\italic "pizz."}
1187 arco = \markup {\italic "arco"}
1188 perd = \markup {\italic "perdend."}
1193 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1194 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1195 %%%%%   REST COMBINATION
1196 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1197 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1201 %% REST COMBINING, TAKEN FROM http://lsr.dsi.unimi.it/LSR/Item?id=336
1203 %% Usage:
1204 %%   \new Staff \with {
1205 %%     \override RestCollision #'positioning-done = #merge-rests-on-positioning
1206 %%   } << \somevoice \\ \othervoice >>
1207 %% or (globally):
1208 %%   \layout {
1209 %%     \context {
1210 %%       \Staff
1211 %%       \override RestCollision #'positioning-done = #merge-rests-on-positioning
1212 %%     }
1213 %%   }
1215 %% Limitations:
1216 %% - only handles two voices
1217 %% - does not handle multi-measure/whole-measure rests
1219 #(define (rest-score r)
1220   (let ((score 0)
1221   (yoff (ly:grob-property-data r 'Y-offset))
1222   (sp (ly:grob-property-data r 'staff-position)))
1223     (if (number? yoff)
1224   (set! score (+ score 2))
1225   (if (eq? yoff 'calculation-in-progress)
1226       (set! score (- score 3))))
1227     (and (number? sp)
1228    (<= 0 2 sp)
1229    (set! score (+ score 2))
1230    (set! score (- score (abs (- 1 sp)))))
1231     score))
1233 #(define (merge-rests-on-positioning grob)
1234   (let* ((can-merge #f)
1235    (elts (ly:grob-object grob 'elements))
1236    (num-elts (and (ly:grob-array? elts)
1237       (ly:grob-array-length elts)))
1238    (two-voice? (= num-elts 2)))
1239     (if two-voice?
1240   (let* ((v1-grob (ly:grob-array-ref elts 0))
1241          (v2-grob (ly:grob-array-ref elts 1))
1242          (v1-rest (ly:grob-object v1-grob 'rest))
1243          (v2-rest (ly:grob-object v2-grob 'rest)))
1244     (and
1245      (ly:grob? v1-rest)
1246      (ly:grob? v2-rest)
1247      (let* ((v1-duration-log (ly:grob-property v1-rest 'duration-log))
1248       (v2-duration-log (ly:grob-property v2-rest 'duration-log))
1249       (v1-dot (ly:grob-object v1-rest 'dot))
1250       (v2-dot (ly:grob-object v2-rest 'dot))
1251       (v1-dot-count (and (ly:grob? v1-dot)
1252              (ly:grob-property v1-dot 'dot-count -1)))
1253       (v2-dot-count (and (ly:grob? v2-dot)
1254              (ly:grob-property v2-dot 'dot-count -1))))
1255        (set! can-merge
1256        (and
1257         (number? v1-duration-log)
1258         (number? v2-duration-log)
1259         (= v1-duration-log v2-duration-log)
1260         (eq? v1-dot-count v2-dot-count)))
1261        (if can-merge
1262      ;; keep the rest that looks best:
1263      (let* ((keep-v1? (>= (rest-score v1-rest)
1264               (rest-score v2-rest)))
1265       (rest-to-keep (if keep-v1? v1-rest v2-rest))
1266       (dot-to-kill (if keep-v1? v2-dot v1-dot)))
1267        ;; uncomment if you're curious of which rest was chosen:
1268        ;;(ly:grob-set-property! v1-rest 'color green)
1269        ;;(ly:grob-set-property! v2-rest 'color blue)
1270        (ly:grob-suicide! (if keep-v1? v2-rest v1-rest))
1271        (if (ly:grob? dot-to-kill)
1272            (ly:grob-suicide! dot-to-kill))
1273        (ly:grob-set-property! rest-to-keep 'direction 0)
1274        (ly:rest::y-offset-callback rest-to-keep)))))))
1275     (if can-merge
1276   #t
1277   (ly:rest-collision::calc-positioning-done grob))))
1283 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1284 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1285 %%%%%   TABLE OF CONTENTS
1286 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1287 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1290 contentsTitle = "Inhalt / Contents"
1292 \paper {
1293   tocTitleMarkup = \markup \fill-line{
1294     \null
1295     \column {
1296       \override #(cons 'line-width (* 7 cm))
1297       \line{ \fill-line {\piece-title {\contentsTitle} \null }}
1298       \hspace #1
1299     }
1300     \null
1301   }
1302   tocItemMarkup = \markup \fill-line {
1303     \null
1304     \column {
1305       \override #(cons 'line-width (* 7 cm ))
1306       \line { \fill-line{\fromproperty #'toc:text \fromproperty #'toc:page }}
1307     }
1308     \null
1309   }
1313 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1314 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1315 %%%%%   TITLE PAGE / HEADER
1316 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1317 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1319 #(define-markup-command (when-property layout props symbol markp) (symbol? markup?)
1320   (if (chain-assoc-get symbol props)
1321       (interpret-markup layout props markp)
1322       (ly:make-stencil '()  '(1 . -1) '(1 . -1))))
1324 #(define-markup-command (vspace layout props amount) (number?)
1325   "This produces a invisible object taking vertical space."
1326   (let ((amount (* amount 3.0)))
1327     (if (> amount 0)
1328         (ly:make-stencil "" (cons -1 1) (cons 0 amount))
1329         (ly:make-stencil "" (cons -1 1) (cons amount amount)))))
1333 titlePageMarkup = \markup \abs-fontsize #10 \when-property #'header:title \column {
1334     \vspace #4
1335     \fill-line { \fontsize #8 \fromproperty #'header:composer }
1336     \vspace #1
1337     \fill-line { \fontsize #8 \fromproperty #'header:poet }
1338     \vspace #4
1339     \fill-line { \fontsize #10 \bold \fromproperty #'header:titlepagetitle }
1340     \vspace #1
1341     \fontsize #2 \when-property #'header:titlepagesubtitle {
1342       \fill-line { \fromproperty #'header:titlepagesubtitle }
1343       \vspace #1
1344     }
1345     \fill-line { \postscript #"-20 0 moveto 40 0 rlineto stroke" }
1346     \vspace #8
1347     \fill-line { \fontsize #5 \fromproperty #'header:ensemble }
1348     \vspace #0.02
1349     \fill-line { \fontsize #2 \fromproperty #'header:instruments }
1350     \vspace #9
1351     \fill-line { \fontsize #5 \fromproperty #'header:date }
1352     \vspace #1
1353     \fill-line { \fontsize #5 \fromproperty #'header:scoretype }
1354     \vspace #1
1355     \when-property #'header:instrument {
1356       \fill-line { \bold \fontsize #6 \rounded-box \fromproperty #'header:instrument }
1357     }
1358     \vspace #7
1359     \fontsize #2 \when-property #'header:enteredby \override #'(baseline-skip . 3.75) \left-align\center-column {
1360       \fill-line { "Herausgegeben von: / Edited by:"}
1361       \vspace #0.
1362       \fill-line { \fromproperty #'header:enteredby }
1363     }
1364     \fill-line {
1365       \when-property #'header:arrangement \column {
1366         \vspace #8
1367         \fill-line { \fontsize #3 \fromproperty #'header:arrangement }
1368       }
1369     }
1370   \vspace #6
1371   \fill-line { \fromproperty #'header:copyright }
1374 titleHeaderMarkup = \markup {
1375   \override #'(baseline-skip . 3.5)
1376   \column {
1377     \fill-line {
1378       \fromproperty #'header:logo
1379       \override #'(baseline-skip . 4.5) \center-column {
1380         \bold \abs-fontsize #18 \fromproperty #'header:title
1381         \bold \abs-fontsize #12 \fromproperty #'header:subtitle
1382         \abs-fontsize #11 \fromproperty #'header:subsubtitle
1383       }
1384       \bold \abs-fontsize #11 \when-property #'header:instrument \rounded-box \fromproperty #'header:instrument
1385     }
1386     \fill-line {
1387       \with-dimensions #'( 0 . 0) #'( 0 . 1 ) \null
1388     }
1390     \fill-line {
1391             \abs-fontsize #10 \fromproperty #'header:poet
1392             \abs-fontsize #10 \fromproperty #'header:composer
1393     }
1394     \fill-line {
1395             \abs-fontsize #10 \fromproperty #'header:meter
1396             \abs-fontsize #10 \fromproperty #'header:arranger
1397     }
1398   }
1402 titleScoreMarkup = \markup \piece-title \fromproperty #'header:piece
1404 \paper {
1405   scoreTitleMarkup = \titleScoreMarkup
1406   bookTitleMarkup = \titleHeaderMarkup
1411 %%%%%%%%%%%%%% headers and footers %%%%%%%%%%%%%%%%%%%%%%%%%%
1413 #(define (first-score-page layout props arg)
1414   (let* ((label 'first-score-page)
1415          (table (ly:output-def-lookup layout 'label-page-table))
1416          (label-page (and (list? table) (assoc label table)))
1417          (page-number (and label-page (cdr label-page)))
1418         )
1419     (if (eq? (chain-assoc-get 'page:page-number props -1) page-number)
1420       (interpret-markup layout props arg)
1421       empty-stencil)))
1423 #(define no-header-table '())
1424 thisPageNoHeader = #(define-music-function (parser location) ()
1425   (let* ((label (gensym "header")))
1426     (set! no-header-table (cons label no-header-table))
1427     (make-music 'Music
1428       'page-marker #t
1429       'page-label label)))
1432 % TODO: Use the no-header-table!
1433 #(define (is-header-page layout props arg)
1434   (let* ((page-number (chain-assoc-get 'page:page-number props -1))
1435         )
1436     ;(if (and (> page-number 2) (!= page-number 7))
1437     (if (> page-number 1)
1438       (interpret-markup layout props arg)
1439       empty-stencil)))
1441 #(define no-footer-table '())
1442 thisPageNoFooter = #(define-music-function (parser location) ()
1443   (let* ((label (gensym "footer")))
1444     (set! no-footer-table (cons label no-footer-table))
1445     (make-music 'Music
1446       'page-marker #t
1447       'page-label label)))
1449 % TODO: Use the no-footer-table!
1450 #(define (is-footer-page layout props arg)
1451   (let* ((page-number (chain-assoc-get 'page:page-number props -1))
1452          (label 'first-score-page)
1453          (table (ly:output-def-lookup layout 'label-page-table))
1454          (label-page (and (list? table) (assoc label table)))
1455          ;(page-number (and label-page (cdr label-page)))
1456         )
1457     (if (and (> page-number 1))
1458       (interpret-markup layout props arg)
1459       empty-stencil)))
1462 #(define copyright-footer-table '())
1463 thisPageCopyrightFooter = #(define-music-function (parser location) ()
1464   (let* ((label (gensym "copyrightfooter")))
1465     (set! copyright-footer-table (cons label copyright-footer-table))
1466     (make-music 'Music
1467       'page-marker #t
1468       'page-label label)))
1470 #(define copyright-pg 1)
1471 #(define (set-copyright-page page)
1472   (set! copyright-pg page)
1475 % TODO: Use the copyright-footer-table!
1476 #(define (copyright-page layout props arg)
1477     (if (= (chain-assoc-get 'page:page-number props -1) copyright-pg)
1478       (interpret-markup layout props arg)
1479       empty-stencil))
1482 \paper {
1483   oddHeaderMarkup = \markup \fill-line {
1484     %% force the header to take some space, otherwise the
1485     %% page layout becomes a complete mess.
1486     " "
1487     \on-the-fly #is-header-page \fromproperty #'header:title
1488     \on-the-fly #is-header-page \fromproperty #'page:page-number-string
1489   }
1490   evenHeaderMarkup = \markup \fill-line {
1491     \on-the-fly #is-header-page \fromproperty #'page:page-number-string
1492     \on-the-fly #is-header-page \fromproperty #'header:composer
1493     " "
1494   }
1496   oddFooterMarkup = \markup {
1497     \column {
1498       \fill-line {
1499         %% publisher header field only on title page.
1500         \on-the-fly #first-page \fromproperty #'header:publisher
1501       }
1502       \fill-line {
1503         %% copyright on the first real score page
1504         \on-the-fly #copyright-page \fromproperty #'header:copyright
1505         \on-the-fly #copyright-page \null
1506       }
1507       \fill-line {
1508         %% All other pages get the number of the edition centered
1509         \on-the-fly #is-footer-page \fromproperty #'header:scorenumber
1510       }
1511     }
1512   }
1526 % Interpret the given markup with the header fields added to the props.
1527 % This way, one can re-use the same functions (using fromproperty
1528 % #'header:field) in the header block and as top-level markup.
1530 % This function is originally copied from mark-up-title (file scm/titling.scm),
1531 % which is lilypond's internal function to handle the title markups. I needed
1532 % to replace the scopes and manually add the $defaultheader (which is internally
1533 % done in paper-book.cc before calling mark-up-title. Also, I don't extract the
1534 % markup from the header block, but use the given markup.
1536 % I'm not sure if I really need the page properties in props, too... But I
1537 % suppose it does not hurt, either.
1538 #(define-markup-command (markupWithHeader layout props markup) (markup?)
1539   "Interpret the given markup with the header fields added to the props.
1540    This way, one can re-use the same functions (using fromproperty
1541    #'header:field) in the header block and as top-level markup."
1542   (let* (
1543       ; TODO: If we are inside a score, add the score's local header block, too!
1544       ; Currently, I only use the global header block, stored in $defaultheader
1545       (scopes (list $defaultheader))
1546       (alists (map ly:module->alist scopes))
1548       (prefixed-alist
1549         (map (lambda (alist)
1550           (map (lambda (entry)
1551             (cons
1552               (string->symbol (string-append "header:" (symbol->string (car entry))))
1553               (cdr entry)))
1554             alist))
1555           alists))
1556       (props (append prefixed-alist
1557               props
1558               (layout-extract-page-properties layout)))
1559     )
1560     (interpret-markup layout props markup)
1561   )
1569 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1570 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1571 %%%%%   Equally spacing multiple columns (e.g. for translations)
1572 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1573 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1575 % Credits: Nicolas Sceaux on the lilypond-user mailinglist
1576 #(define-markup-command (columns layout props args) (markup-list?)
1577    (let ((line-width (/ (chain-assoc-get 'line-width props
1578                          (ly:output-def-lookup layout 'line-width))
1579                         (max (length args) 1))))
1580      (interpret-markup layout props
1581        (make-line-markup (map (lambda (line)
1582                                 (markup #:pad-to-box `(0 . ,line-width) '(0 . 0)
1583                                   #:override `(line-width . ,line-width)
1584                                   line))
1585                                args)))))
1589 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1590 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1591 %%%%%   SCORE (HEADER / LAYOUT) SETTINGS
1592 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1593 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1596 startSlashedGraceMusic =  {
1597   \override Stem  #'stroke-style = #"grace"
1600 stopSlashedGraceMusic =  {
1601   \revert Stem #'stroke-style
1604 slashedGrace =
1605 #(def-grace-function startSlashedGraceMusic stopSlashedGraceMusic
1606    (_i "Create slashed graces (slashes through stems, but no slur)from the following music expression"))
1609 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1610 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1611 %%%%%   SCORE (HEADER / LAYOUT) SETTINGS
1612 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1613 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1615 \paper {
1616   footnote-separator-markup = \markup { \fill-line { \override #`(span-factor . 1/4) { \draw-hline } \null }}
1618   left-margin = 2\cm
1619   right-margin = 1.5\cm
1620   line-width = 17.5\cm
1621 %   bottom-margin = 1.5\cm
1622   top-margin = 0.7\cm
1623 %   after-title-space = 0.5\cm
1624   ragged-right = ##f
1625   ragged-last = ##f
1626   ragged-bottom = ##f
1627   ragged-last-bottom = ##f
1629 \layout {
1630   \context {
1631     \ChoirStaff
1632     % If only one non-empty staff in a system exists, still print the backet
1633     \override SystemStartBracket #'collapse-height = #1
1634     \consists "Instrument_name_engraver"
1635     \consists "Keep_alive_together_engraver"
1636   }
1637   \context {
1638     \StaffGroup
1639     % If only one non-empty staff in a system exists, still print the backet
1640     \override SystemStartBracket #'collapse-height = #1
1641     \consists "Instrument_name_engraver"
1642   }
1643   \context {
1644     \GrandStaff
1645     \override SystemStartBracket #'collapse-height = #1
1646     \consists "Instrument_name_engraver"
1647   }
1648   \context {
1649     \FiguredBass
1650 %     \override VerticalAxisGroup #'keep-fixed-while-stretching = ##t
1651 %     \override VerticalAxisGroup #'minimum-Y-extent  = #'(0 . 1) % TODO: Removed
1652     \override VerticalAxisGroup #'padding = #0
1653   }
1654   \context {
1655     \Score
1656     % Force multi-measure rests to be written as one span
1657     \override MultiMeasureRest #'expand-limit = #3
1658     skipBars = ##t
1659     autoBeaming = ##f
1660 %     \override Hairpin #'to-barline = ##f
1661 %     \override BarNumber #'break-visibility = #end-of-line-invisible
1662 %     \override BarNumber #'self-alignment-X = #0
1663 %     barNumberVisibility = #(every-nth-bar-number-visible 5)
1664     \override CombineTextScript #'avoid-slur = #'outside
1665     \override DynamicTextSpanner #'dash-period = #-1.0
1666     \override InstrumentSwitch #'font-size = #-1
1668     % Rest collision
1669     \override RestCollision #'positioning-done = #merge-rests-on-positioning
1670     % Auto-Accidentals: Use modern-cautionary style...
1671     extraNatural = ##f
1672     % Accidental rules (the rule giving the most accidentals wins!)
1673     % -) Reset accidentals at each barline -> accs not in key sig will always be printed
1674     % -) Same octave accidentals are remembered for two measures -> cancellation
1675     % -) other octave accidentals are remembered for next measure -> cancellation
1676     autoAccidentals = #`(Staff  ,(make-accidental-rule 'same-octave 0)
1677                                 ,(make-accidental-rule 'any-octave 0)
1678                                 ,(make-accidental-rule 'any-octave 1)
1679                                 ,(make-accidental-rule 'same-octave 2))
1680     % No auto-cautionaries, we always use autoAccidentals!
1681 %     autoCautionaries = #`(Staff ,(make-accidental-rule 'any-octave 0)
1682 %                                 ,(make-accidental-rule 'same-octave 1))
1683     printKeyCancellation = ##t
1684     quotedEventTypes = #'(StreamEvent)
1685     quotedCueEventTypes = #'(
1686       rhythmic-event
1687       tie-event
1688       beam-event
1689       tuplet-span-event
1690       tremolo-event
1691       glissando-event
1692       harmonic-event
1693       repeat-tie-event
1694       articulation-event
1695       slur-event
1696       trill-span-event
1697       tremolo-span-event
1698     )
1699     implicitBassFigures = #'(0 100)
1700   }
1701   \context {
1702     \Staff
1703     \RemoveEmptyStaves
1704   }
1708 ts = #(make-music 'TextScriptEvent 'text "t.s." 'direction UP )
1709 tt = #(make-music 'TextScriptEvent 'text "Tutti" 'direction UP )
1710 solo = #(make-music 'TextScriptEvent 'text "Solo" 'direction UP )
1711 tutti = #(make-music 'TextScriptEvent 'text "Tutti" 'direction UP )
1712 bracketts = #(make-music 'TextScriptEvent 'text "[t.s.]" 'direction UP )
1713 brackettt = #(make-music 'TextScriptEvent 'text "[Tutti]" 'direction UP )
1714 bracketsolo = #(make-music 'TextScriptEvent 'text "[Solo]" 'direction UP )
1716 sottovoce = #(make-music 'TextScriptEvent 'text "sotto voce" 'direction UP )
1718 dashedSlur = -\tweak #'dash-definition #'((0 1 0.4 0.75))(
1719 dashedTie = -\tweak #'dash-definition #'((0 1 0.4 0.75))~
1721 divisi = #(define-music-function (parser location vc1 vc2) (ly:music? ly:music?)
1723   << { \voiceOne $vc1 \oneVoice} \context Voice = "divisi2" { \voiceTwo $vc2 } >>
1727 #(define twoVoice divisi)
1729 #(define-public (bracket-stencils grob)
1730   (let ((lp (grob-interpret-markup grob (markup #:fontsize 3.5 #:translate (cons -0.3 -0.5) "[")))
1731         (rp (grob-interpret-markup grob (markup #:fontsize 3.5 #:translate (cons -0.3 -0.5) "]"))))
1732     (list lp rp)))
1734 bracketify = #(define-music-function (parser loc arg) (ly:music?)
1735    (_i "Tag @var{arg} to be parenthesized.")
1737   \once \override ParenthesesItem #'stencils = #bracket-stencils
1738   \parenthesize $arg
1743 #(define-markup-command (hat layout props arg) (markup?)
1744   "Draw a hat above the given string @var{arg}."
1745   (interpret-markup layout props (markup #:combine #:raise 1.5 "^" arg)))
1749 smallFlageolet =
1750 #(let ((m (make-music 'ArticulationEvent
1751                       'articulation-type "flageolet")))
1752    (ly:music-set-property! m 'tweaks
1753      (acons 'font-size -2
1754        (ly:music-property m 'tweaks)))
1755   m)
1758 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1759 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1760 %%%%%   LICENSE TEXTS
1761 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1762 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1764 LicenseCCBYPlain = \markup {Creative Commons BY \with-url #"http://creativecommons.org/licenses/by/3.0/at/" {\translate #'(0 . -0.7) \epsfile #Y #3 #"orchestrallily/cc-by.eps" }}
1765 LicenseCCBY = \markup {Lizensiert unter / Licensed under: Creative Commons BY \with-url #"http://creativecommons.org/licenses/by/3.0/at/" {\translate #'(0 . -0.7) \epsfile #Y #3 #"orchestrallily/cc-by.eps" }}
1766 LicenseCCBYNC = \markup {Lizensiert unter / Licensed under: Creative Commons BY-NC \with-url #"http://creativecommons.org/licenses/by-nc/3.0/at/" {\translate #'(0 . -0.7) \epsfile #Y #3 #"orchestrallily/cc-by-nc.eps" }}
1767 LicenseNoRestrictions = \markup{\line {Die Ausgabe darf kopiert und ohne Einschränkungen aufgeführt werden. / May be copied and performed without restriction.}}
1769 \include "sceaux_clef-key.ily"
1772 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1773 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1774 %%%%%   VARIOUS
1775 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1776 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1778 startUnremovableSection = \set Staff.keepAliveInterfaces =
1779  #'(rhythmic-grob-interface
1780     rest-interface
1781     lyric-interface
1782     percent-repeat-item-interface
1783     percent-repeat-interface
1784     stanza-number-interface)
1786 endUnremovableSection = \unset Staff.keepAliveInterfaces
1789 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1790 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1791 %%%%%   EDITORIAL ANNOTATIONS
1792 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1793 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1795 #(define-public (editorial-bracket-stencil stil padding widen)
1796 "Add brackets for editorial annoations around STIL, producing a new stencil."
1797 (let* ((axis Y)
1798        (other-axis (lambda (a) (remainder (+ a 1) 2)))
1799        (ext (interval-widen (ly:stencil-extent stil axis) widen))
1800        (thick 0.15)
1801        (protrusion 0.3)
1802        (lb (ly:bracket axis ext thick protrusion))
1803        (rb (ly:bracket axis ext thick (- protrusion))))
1804   (set! stil (ly:stencil-combine-at-edge stil (other-axis axis) 1 rb padding))
1805   (set! stil
1806     (ly:stencil-combine-at-edge lb (other-axis axis) 1 stil padding))
1807   stil))
1809 editorialHairpin = \once \override Hairpin     #'stencil = #(lambda (grob) (editorial-bracket-stencil (ly:hairpin::print grob) 0.2 0.55))
1810 editorialDynamic = \once \override DynamicText #'stencil = #(lambda (grob) (editorial-bracket-stencil (ly:text-interface::print grob) 0.2 0.55))
1811 editorialMarkup =  \once \override TextScript  #'stencil = #(lambda (grob) (editorial-bracket-stencil (ly:text-interface::print grob) 0.2 0.55))
1813 % videStart = \mark \markup { \hspace #1 \musicglyph #"scripts.coda"  \with-dimensions #'(0 . 0) #'(0 . 0) \left-align { vi-} }
1814 videStart = \mark \markup \halign #-2.3 \concat { \hspace #4.5 \musicglyph #"scripts.coda" \left-align { vi- } }
1815 % videEnd = \notemode {
1816 %   \once \override Score.RehearsalMark #'break-visibility = #begin-of-line-invisible
1817 %   \mark \markup \concat{ \with-dimensions #'(0 . 0) #'(0 . 0) \right-align { -de } \hspace #1 \musicglyph #"scripts.coda" }
1819 videEnd = \notemode {
1820         \once \override Score.RehearsalMark #'break-visibility = #begin-of-line-invisible
1821         \mark \markup \concat{ \right-align { -de } \hspace #1.5 \musicglyph #"scripts.coda" \hspace #4.2 }
1826 \layout {
1827         \context {\Staff
1828                 soloText = #"I"
1829                 soloIIText = #"II"
1830                 aDueText = #"a2"
1831         }
1834 \paper {
1835 %   annotate-spacing = ##t
1836   ragged-bottom = ##f
1837   ragged-last = ##f
1838   ragged-last-bottom = ##f
1840   top-markup-spacing #'minimum-distance = #5
1841 %   top-markup-spacing #'space = #4
1842 %   top-markup-spacing #'padding = #2
1843   top-markup-spacing #'stretchability = #15
1845   top-system-spacing #'minimum-distance = #0
1846 %   top-system-spacing #'space = #3
1847   top-system-spacing #'padding = #2
1848   top-system-spacing #'stretchability = #13
1849   
1850   markup-system-spacing #'minimum-distance = #5
1851 %   markup-system-spacing #'space = #4
1852   markup-system-spacing #'padding = #3
1853   markup-system-spacing #'stretchability = #25
1854   
1855   system-system-spacing #'minimum-distance = #0
1856 %   system-system-spacing #'space = #5
1857   system-system-spacing #'padding = #2
1858   system-system-spacing #'stretchability = #15
1859   
1860   last-bottom-spacing #'basic-distance = #3
1861 %   last-bottom-spacing #'space = #7
1862   last-bottom-spacing #'padding = #4
1863   last-bottom-spacing #'stretchability = #14
1865 %   score-markup-spacing #'space = #5
1866 %   score-markup-spacing #'stretchability = #15
1868 %   markup-markup-spacing #'space = #5
1869 %   markup-markup-spacing #'stretchability = #30
1872 \layout {
1873   \context { \PianoStaff
1874     \override StaffGrouper #'staff-staff-spacing #'stretchability = #1.5
1875   }
1876   \context { \StaffGroup
1877     \override StaffGrouper #'staff-staff-spacing #'stretchability = #2.5
1878     \override SystemStartBracket #'collapse-height = #1
1879   }
1880   \context { \GrandStaff
1881     \override StaffGrouper #'staff-staff-spacing #'stretchability = #3
1882     \override StaffGrouper #'staffgroup-staff-spacing #'stretchability = #3
1883     \override StaffGrouper #'staff-staffgroup-spacing #'stretchability = #3
1884    }
1885   \context { \ChoirStaff
1886     \override StaffGrouper #'staff-staff-spacing #'stretchability = #1
1887   }
1888   \context { \Staff
1889     \override StaffGrouper #'staff-staff-spacing #'stretchability = #4.9
1890   }
1891   \context { \Score
1892     \override StaffGrouper #'staff-staff-spacing #'stretchability = #5
1893   }
1898 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1899 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1900 %%%%%   WORKAROUNDS!
1901 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1902 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1904 % _ does not work as a direction modifier in figured bass
1905 tsdown = #(make-music 'TextScriptEvent 'text "t.s." 'direction DOWN )