Add colarco markup
[orchestrallily.git] / orchestrallily.ily
blob6e67f90fb60ecff4c3fc8391ba7b530ec1ec6474
1 \version "2.15.19"
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" ("SoloChoirScore" "O"))
180   ("VocalScore" "SimultaneousMusic" ("SoloChoirScore" "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 % extract the pitch from the music (can also be a raw pitch object!)
254 #(define (oly:extractPitch music)
255   (let* (
256          (elems  (if (ly:music? music) (ly:music-property music 'elements)))
257          (note   (if (pair? elems) (car elems)))
258          (mpitch (if (ly:music? note) (ly:music-property note 'pitch)))
259          (pitch  (if (ly:pitch? music) music mpitch))
260         )
261     (if (and (not-null? music) (not (ly:pitch? pitch)))
262       (ly:warning "Unable to interpret as a pitch!")
263     )
264     pitch
265   )
268 #(define (oly:extractTranspositionPitch piece name)
269   (let* (
270          (trpFromPitch (oly:extractPitch (namedPieceInstrObject piece name "TransposeFrom")))
271          (trpToPitch   (oly:extractPitch (namedPieceInstrObject piece name "TransposeTo")))
272         )
273     (if (ly:pitch? trpFromPitch)
274       (if (ly:pitch? trpToPitch)
275         ; Both pitches
276         (ly:pitch-diff trpFromPitch trpToPitch)
277         (ly:pitch-diff trpFromPitch (ly:make-pitch 0 0 0))
278       )
279       (if (ly:pitch? trpToPitch)
280         (ly:pitch-diff (ly:make-pitch 0 0 0) trpToPitch)
281         #f
282       )
283     )
284   )
288 %%=====================================================================
289 %% Extract context modifications for given objects
290 %%---------------------------------------------------------------------
293 % TODO: join these property extractors to avoid code duplication
295 % Generate the properties for the lyrics for piece and instr.
296 % Also check whether we have a modifications object to fech mods from.
297 % return a (possibly empty) list of all assignments.
298 #(define (oly:lyrics_handler_properties piece name lyricsid)
299   (let* (
300          (mods (namedPieceInstrObject piece name (string-append lyricsid "Modifications")))
301          (mod-list (if (not-null? mods) (ly:get-context-mods mods) '()))
302          (mapping '(
303              ;(instrumentName . "InstrumentName")
304              ;(shortInstrumentName . "ShortInstrumentName")
305              ;(midiInstrument . "MidiInstrument")
306             ))
307          (assignments (map
308              (lambda (pr)
309                  (oly:generate_property_pair (car pr) piece name (cdr pr))
310              )
311              mapping))
312          (olyprops (filter not-null? assignments))
313          (props (append mod-list olyprops))
314         )
315     props
316   )
319 % Generate the properties for the voice for piece and instr.
320 % Also check whether we have a modifications object to fech mods from.
321 % return a (possibly empty) list of all assignments.
322 #(define (oly:voice_handler_properties piece name)
323   (let* (
324          (mods (namedPieceInstrObject piece name "VoiceModifications"))
325          (mod-list (if (not-null? mods) (ly:get-context-mods mods) '()))
326          (mapping '(
327              ;(instrumentName . "InstrumentName")
328              ;(shortInstrumentName . "ShortInstrumentName")
329              ;(midiInstrument . "MidiInstrument")
330             ))
331          (assignments (map
332              (lambda (pr)
333                  (oly:generate_property_pair (car pr) piece name (cdr pr))
334              )
335              mapping))
336          (olyprops (filter not-null? assignments))
337          (props (append mod-list olyprops))
338         )
339     props
340   )
343 % Generate the properties for the staff for piece and instr. Typically, these
344 % are the instrument name and the short instrument name (if defined).
345 % Also check whether we have a modifications object to fech mods from.
346 % return a (possibly empty) list of all assignments.
347 #(define (oly:staff_handler_properties piece instr)
348   (let* (
349          (mods (namedPieceInstrObject piece instr "StaffModifications"))
350          (mod-list (if (not-null? mods) (ly:get-context-mods mods) '()))
351          (mapping '(
352               (instrumentName . "InstrumentName")
353               (shortInstrumentName . "ShortInstrumentName")
354               (midiInstrument . "MidiInstrument")
355             ))
356          (assignments (map
357              (lambda (pr)
358                  (oly:generate_property_pair (car pr) piece instr (cdr pr))
359              )
360              mapping))
361          (olyprops (filter not-null? assignments))
362          (props (append mod-list olyprops))
363         )
364     props
365   )
371 %%=====================================================================
372 %% Extract contents for voices
373 %%---------------------------------------------------------------------
375 #(define (oly:musiccontent_for_voice parser piece name music additional)
376   (let* ((musiccontent additional))
378     ; Append the settings, key and clef (if defined)
379     (map
380       (lambda (type)
381         (let* ((object (namedPieceInstrObject piece name type)))
382           (if (ly:music? object)
383             (set! musiccontent (append musiccontent (list (ly:music-deep-copy object))))
384             (if (not-null? object) (ly:warning (_ "Wrong type (no ly:music) for ~S for instrument ~S in piece ~S") type name piece))
385           )
386         )
387       )
388       ; TODO: Does the "Tempo" work here???
389       '("Settings" "Key" "Clef" "TimeSignature" "ExtraSettings";"Tempo"
390       )
391     )
393     (if (ly:music? music)
394       (begin
395         (set! musiccontent (make-sequential-music (append musiccontent (list music))))
396         ;(ly:message "Generating staff for ~a" name)
397         (let* ((trpPitch (oly:extractTranspositionPitch piece name)))
398           (if (ly:pitch? trpPitch)
399             (set! musiccontent (ly:music-transpose musiccontent trpPitch))
400           )
401         )
402         musiccontent
403       )
404       ; For empty music, return empty
405       '()
406     )
407   )
412 %%=====================================================================
413 %% create Lyrics
414 %%---------------------------------------------------------------------
417 #(define (oly:lyrics_create_single_context parser piece name voicename lyricsid)
418   ; If we have lyrics, create a lyrics context containing LyricCombineMusic
419   ; and add that as second element to the staff's elements list...
420   ; Also add possibly configured LyricsModifications
421   (let* ((id (string-append "Lyrics" lyricsid))
422          (lyricsmods (oly:lyrics_handler_properties piece name id))
423          (lyrics (namedPieceInstrObject piece name id))
424          (ctx (if (ly:music? lyrics)
425                   (context-spec-music (make-music 'LyricCombineMusic
426                                                   'element lyrics
427                                                   'associated-context voicename)
428                                       'Lyrics
429                                       (oly:generate_object_name piece name id))
430                   '())))
431     (if (and (not-null? lyricsmods) (not-null? ctx))
432       (set! (ly:music-property ctx 'property-operations) lyricsmods)
433     )
434     ctx
435   )
438 #(define (oly:lyrics_create_contexts parser piece name voicename)
439   (filter not-null?
440     (map (lambda (str)
441                  (oly:lyrics_create_single_context parser piece name voicename str))
442          (list "" "I" "II" "III"  "IV" "V" "VI"))))
445 %%=====================================================================
446 %% Voice handling
447 %%---------------------------------------------------------------------
450 #(define (oly:voice_handler_internal parser piece name type music)
451   (if (ly:music? music)
452     (let* (
453            (voicename    (oly:generate_object_name piece name "Voice" ))
454            (lyrics       (oly:lyrics_create_contexts parser piece name voicename))
455            (additional   (if (not-null? lyrics) (list dynamicUp) '()))
456            (musiccontent (oly:musiccontent_for_voice parser piece name music additional))
457            (voicetype    (oly:staff_type type))
458            (voice        (context-spec-music musiccontent voicetype voicename))
459            (voiceprops   (oly:voice_handler_properties piece name))
460           )
461       (if (not-null? voiceprops)
462         (set! (ly:music-property voice 'property-operations) voiceprops)
463       )
464       (cons voice lyrics)
465     )
466     ; For empty music, return empty
467     '()
468   )
471 #(define (oly:voice_handler parser piece name type)
472   (oly:voice_handler_internal parser piece name type (oly:get_music_object piece name)))
475 %%=====================================================================
476 %% Staff/Group handling
477 %%---------------------------------------------------------------------
480 #(define (oly:staff_handler_internal parser piece name type voices)
481   (if (not-null? voices)
482     (let* (
483            (staffname  (oly:generate_staff_name piece name))
484            (stafftype  (oly:staff_type type))
485            (staff      (make-simultaneous-music voices))
486            (propops    (oly:staff_handler_properties piece name))
487           )
488       (case stafftype
489         ((SimultaneousMusic ParallelMusic) #f)
490         (else (set! staff (context-spec-music staff stafftype staffname)))
491       )
492       (if (not-null? propops)
493         (set! (ly:music-property staff 'property-operations) propops)
494       )
495       staff
496     )
497     ; For empty music, return empty
498     '()
499   )
502 #(define (oly:staff_handler parser piece name type children)
503   (let* ((c (if (not-null? children) children (list name)))
504          (voices (apply append (map (lambda (v) (oly:create_voice parser piece v)) c)) )
505         )
506     (if (not-null? voices)
507       (oly:staff_handler_internal parser piece name type voices)
508       '()
509     )
510   )
513 #(define (oly:devnull_handler parser piece name type children)
514   (oly:voice_handler parser piece name type)
517 #(define (oly:parallel_voices_staff_handler parser piece name type children)
518   (let* (
519          (voices (map (lambda (i) (oly:create_voice parser piece i)) children))
520          ; get the list of non-empty voices and flatten it!
521          (nonemptyvoices (apply append (filter not-null? voices)))
522         )
523     (if (not-null? nonemptyvoices)
524       (oly:staff_handler_internal parser piece name "Staff" nonemptyvoices)
525       '()
526     )
527   )
530 #(define (oly:remove-with-tag tag music)
531   (if (ly:music? music)
532       (music-filter
533         (lambda (m)
534           (let* ((tags (ly:music-property m 'tags))
535                  (res (memq tag tags)))
536             (not res)))
537         music)
538       music))
540 % Remove all music tagged a not-part-combine
541 #(define (oly:remove-non-part-combine-events music)
542   (oly:remove-with-tag 'non-partcombine music))
544 #(define (oly:part_combined_staff_handler parser piece name type children)
545   (let* ((rawmusic (map (lambda (c) (oly:musiccontent_for_voice parser piece name (oly:get_music_object piece c) '())) children))
546          (filteredmusic (map (lambda (m) (oly:remove-non-part-combine-events m)) rawmusic))
547          (music (filter not-null? filteredmusic)))
548   (cond
549       ((and (pair? music) (ly:music? (car music)) (not-null? (cdr music)) (ly:music? (cadr music)))
550           ;(ly:message "Part-combine with two music expressions")
551           (oly:staff_handler_internal parser piece name "Staff" (list (make-part-combine-music parser music #f))))
552       ((null? music)
553           ;;(ly:warning "Part-combine without any music expressions")
554           '())
555       ; exactly one is a music expression, simply use that by joining
556       ((list? music)
557           ;;(ly:message "Part-combine with only one music expressions")
558           (oly:staff_handler_internal parser piece name "Staff" (list (apply append music))))
559       (else
560           ;(ly:message "make_part_combined_staff: ~S ~S ~a" piece instr instruments)
561           '() )
562     )
563   )
566 % Figured bass is a special case, as it can be voice- or staff-type. When
567 % given as a staff type, simply call the voice handler, instead
569 #(define (oly:figured_bass_staff_handler parser piece name type children)
570   (let* ((c (if (not-null? children) children (list name)))
571          (voice  (oly:voice_handler parser piece (car c) type)))
572     (if (pair? voice) (car voice) ())
573   )
576 #(define (flatten lst)
577   (define (f remaining result)
578     (cond
579       ((null? remaining) result)
580       ((pair? (car remaining)) (f (cdr remaining) (f (car remaining) result)))
581       (else (f (cdr remaining) (cons (car remaining) result)))))
582   (reverse! (f lst '())))
584 #(define (oly:staff_group_handler parser piece name type children)
585   (let* (
586          (staves (flatten (map (lambda (i) (oly:create_staff_or_group parser piece i)) children)))
587          (nonemptystaves (filter not-null? staves))
588         )
589     (if (not-null? nonemptystaves)
590       (let* (
591              (musicexpr (if (= 1 (length nonemptystaves))
592                           (car nonemptystaves)
593                           (make-simultaneous-music nonemptystaves)))
594              (groupname (oly:generate_staff_name piece name))
595              (grouptype (oly:staff_type type))
596              (group     musicexpr)
597              (propops   (oly:staff_handler_properties piece name))
598             )
599         (case grouptype
600           ((SimultaneousMusic ParallelMusic) #f)
601           (else (set! group (context-spec-music group grouptype groupname)))
602         )
603         (if (pair? propops)
604           (set! (ly:music-property group 'property-operations) propops))
605         group
606       )
607       ; Return empty list if no staves are generated
608       '()
609     )
610   )
613 #(define (oly:create_voice parser piece name)
614   (let* ( (voice (namedPieceInstrObject piece name "Voice"))
615           (type (assoc-ref oly:voice_types name)) )
616     (if (not-null? voice)
617       ; Explicit voice variable, use that
618       voice
620       (if (not type)
621         ; No entry in structure found => simple voice
622         (oly:voice_handler parser piece name "Voice")
623         ; Entry found in structure => use the handler for the given type
624         (let* (
625                (voicetype (car type))
626                (handler (assoc-ref oly:voice_handlers voicetype))
627               )
628           (if handler
629             ((primitive-eval handler) parser piece name voicetype)
630             (begin
631               (ly:warning "No handler found for voice type ~a, using default voice handler" voicetype)
632               (oly:voice_handler parser piece name voicetype)
633             )
634           )
635         )
636       )
637     )
638   )
641 #(define (oly:create_staff_or_group parser piece name)
642   (let* ( (staff (namedPieceInstrObject piece name "Staff"))
643           (type_from_structure (assoc-ref oly:orchestral_score_structure name)) )
644     ;(if (not-null? staff)
645     ;  (ly:message "Found staff variable for instrument ~a in piece ~a"  instr piece)
646     ;  (ly:message "Staff variable for instrument ~a in piece ~a NOT FOUND"  instr piece)
647     ;)
648     (if (not-null? staff)
649       ; Explicit staff variable, use that
650       staff
652       (if (not (list? type_from_structure))
653         ; No entry in structure found => simple staff
654         (oly:staff_handler parser piece name "Staff" '())
656         ; Entry found in structure => use the handler for the given type
657         (let* ((type (car type_from_structure))
658                (handler (assoc-ref oly:staff_handlers type))
659                (children (cadr type_from_structure))
660               )
661           (if handler
662             ((primitive-eval handler) parser piece name type children)
663             (begin
664               (ly:warning "No handler found for staff type ~a, using default staff handler" type)
665               (oly:staff_handler parser piece name type children)
666             )
667           )
668         )
669       )
670     )
671   )
674 #(define (oly:dynamics_handler parser piece name type children)
675   (oly:voice_handler parser piece name type)
679 %%=====================================================================
680 %% Handler definitions
681 %%---------------------------------------------------------------------
683 #(define oly:staff_handlers
684   (list
685     ; staff group types
686     '("GrandStaff" . oly:staff_group_handler )
687     '("PianoStaff" . oly:staff_group_handler )
688     '("ChoirStaff" . oly:staff_group_handler )
689     '("StaffGroup" . oly:staff_group_handler )
690     '("ParallelMusic" . oly:staff_group_handler )
691     '("SimultaneousMusic" . oly:staff_group_handler )
692     ; staff types
693     '("Staff" . oly:staff_handler )
694     '("DrumStaff" . oly:staff_handler )
695     '("RhythmicStaff" . oly:staff_handler )
696     '("TabStaff" . oly:staff_handler )
697     '("GregorianTranscriptionStaff" . oly:staff_handler )
698     '("MensuralStaff" . oly:staff_handler )
699     '("VaticanaStaff" . oly:staff_handler )
700     '("ChordNames" . oly:staff_handler )
701     ; staves with multiple voices
702     '("PartCombinedStaff" . oly:part_combined_staff_handler )
703     '("ParallelVoicesStaff" . oly:parallel_voices_staff_handler )
704     ; special cases: Figured bass can be staff or voice type!
705     '("FiguredBass" . oly:figured_bass_staff_handler )
706     ; Devnull is like a staff, only that it doesn't craete output
707     '("Devnull" . oly:devnull_handler )
708     '("Dynamics" . oly:dynamics_handler )
709   )
712 #(define oly:voice_handlers
713   (list
714     ; voice types
715     '("Voice" . oly:voice_handler )
716     '("CueVoice" . oly:voice_handler )
717     '("DrumVoice" . oly:voice_handler )
718     '("FiguredBass" . oly:voice_handler )
719     '("ChordNames" . oly:voice_handler )
720     '("GregorianTranscriptionVoice" . oly:voice_handler )
721     '("NoteNames" . oly:voice_handler )
722     '("TabVoice" . oly:voice_handler )
723     '("VaticanaVoice" . oly:voice_handler )
724   )
728 #(define (oly:register_staff_type_handler type func)
729 ;  (ly:message "Registering staff handler ~a for type ~a" func type)
730   (set! oly:staff_handlers (assoc-set! oly:staff_handlers type func))
733 #(define (oly:register_voice_type_handler type func)
734 ;  (ly:message "Registering voice type handler ~a for type ~a" func type)
735   (set! oly:voice_handlers (assoc-set! oly:voice_handlers type func))
738 % handlers for deprecated API
739 #(oly:register_staff_type_handler 'StaffGroup 'oly:staff_group_handler)
740 #(oly:register_staff_type_handler 'GrandStaff 'oly:staff_group_handler)
741 #(oly:register_staff_type_handler 'PianoStaff 'oly:staff_group_handler)
742 #(oly:register_staff_type_handler 'ChoirStaff 'oly:staff_group_handler)
743 #(oly:register_staff_type_handler 'Staff 'oly:staff_handler )
744 #(oly:register_staff_type_handler 'ParallelMusic 'oly:staff_group_handler)
745 #(oly:register_staff_type_handler 'SimultaneousMusic 'oly:staff_group_handler)
746 #(oly:register_staff_type_handler #t 'oly:part_combined_staff_handler )
747 #(oly:register_staff_type_handler #f 'oly:parallel_voices_staff_handler )
751 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
752 % Automatic score generation
753 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
755 #(define oly:score_handler add-score)
756 #(define oly:music_handler add-music)
757 #(define oly:text_handler add-text)
760 % TODO: deprecate
761 setUseBook = #(define-music-function (parser location usebook) (boolean?)
762   (ly:warning "\\setUseBook has been deprecated! Books are now automatically handled without any hacks")
763   (make-music 'Music 'void #t)
767 % Two functions to handle midi-blocks: Either don't set one, or set an empty
768 % one so that MIDI is generated
769 #(define (oly:set_no_midi_block score) '())
770 #(define (oly:set_midi_block score)
771   (let* ((midiblock (if (defined? '$defaultmidi)
772                         (ly:output-def-clone $defaultmidi)
773                         (ly:make-output-def))))
774     (ly:output-def-set-variable! midiblock 'is-midi #t)
775     (ly:score-add-output-def! score midiblock)
776   )
779 % \setCreateMidi ##t/##f sets a flag to determine wheter MIDI output should
780 % be generated
781 #(define oly:apply_score_midi oly:set_no_midi_block)
782 setCreateMIDI = #(define-music-function (parser location createmidi) (boolean?)
783   (if createmidi
784     (set! oly:apply_score_midi oly:set_midi_block)
785     (set! oly:apply_score_midi oly:set_no_midi_block)
786   )
787   (make-music 'Music 'void #t)
791 % Two functions to handle layout-blocks: Either don't set one, or set an empty
792 % one so that a PDF is generated
793 #(define (oly:set_no_layout_block score) '())
794 #(define (oly:set_layout_block score)
795   (let* ((layoutblock (if (defined? '$defaultlayout)
796                         (ly:output-def-clone $defaultlayout)
797                         (ly:make-output-def))))
798     (ly:output-def-set-variable! layoutblock 'is-layout #t)
799     (ly:score-add-output-def! score layoutblock)
800   )
803 % \setCreatePDF ##t/##f sets a flag to determine wheter PDF output should
804 % be generated
805 #(define oly:apply_score_layout oly:set_no_layout_block)
806 setCreatePDF = #(define-music-function (parser location createlayout) (boolean?)
807   (if createlayout
808     (set! oly:apply_score_layout oly:set_layout_block)
809     (set! oly:apply_score_layout oly:set_no_layout_block)
810   )
811   (make-music 'Music 'void #t)
815 % Set the piece title in a new header block.
816 #(define (oly:set_piece_header score piecename)
817   (if (not-null? piecename)
818     (let* ((header (make-module)))
819       (module-define! header 'piece piecename)
820       (ly:score-set-header! score header)
821     )
822   )
826 % post-filter functions. By default, no filtering is done. However,
827 % for the *NoCues* function, the cue notes should be killed
828 keepcuefilter = #(define-music-function (parser location music) (ly:music?)
829   ((ly:music-function-extract removeWithTag) parser location 'non-cued music))
830 removecuefilter = #(define-music-function (parser location music) (ly:music?)
831   ((ly:music-function-extract removeWithTag) parser location 'cued ((ly:music-function-extract killCues) parser location music)))
833 %% The page numbers are pages counts in the pdf file, not visible page number!
834 %% So we have to offset them if the first page is not page #1
835 %% unfortunately this means we have to store the first-page-number of the first
836 %% bookpart in a global variable, because in later layouts we don't have that
837 %% information available any more (first-page-number will be the first page
838 %% number of the currently processed bookpart!)
839 #(define oly:first-page-offset #f)
840 #(define (oly:create-toc-file layout pages)
841   (if (not oly:first-page-offset)
842       (set! oly:first-page-offset (1- (ly:output-def-lookup layout 'first-page-number))))
843   (let* ((label-table (ly:output-def-lookup layout 'label-page-table)))
844     (if (not (null? label-table))
845       (let* ((format-line (lambda (toc-item)
846              (let* ((label (car toc-item))
847                     (text  (caddr toc-item))
848                     (label-page (and (list? label-table)
849                                      (assoc label label-table)))
850                     (page (and label-page (cdr label-page))))
851                (if page
852                    (format #f "~a, section, 1, {~a}, ~a" (- page oly:first-page-offset) text label)
853                    ;; label came from a different bookpart, so ignore it!
854                    #f))))
855              (formatted-toc-items (map format-line (toc-items)))
856              (whole-string (string-join (filter (lambda (i) i) formatted-toc-items) ",\n"))
857              (output-name (ly:parser-output-name parser))
858              (outfilename (format "~a.toc" output-name))
859              (outfile (open-output-file outfilename)))
860         (if (output-port? outfile)
861             (display whole-string outfile)
862             (ly:warning (_ "Unable to open output file ~a for the TOC information") outfilename))
863         (close-output-port outfile)))))
866 #(define-public (oly:add-toc-item parser markup-symbol text)
867   (oly:music_handler parser (add-toc-item! markup-symbol text)))
870 #(define (oly:add-score parser score piecename)
871   (if (not-null? piecename)
872     (oly:add-toc-item parser 'tocItemMarkup piecename))
873   (oly:score_handler parser score)
875 % The helper function to build a score.
876 #(define (oly:createScoreHelper parser location piece children func)
877   (let* (
878          (staves    (oly:staff_group_handler parser piece "" "SimultaneousMusic" children))
879          (music     (if (not-null? staves)
880                         ((ly:music-function-extract func) parser location staves)
881                         '()
882                     ))
883          (score     '())
884          (piecename (namedPieceInstrObject piece (car children) "PieceName"))
885          (piecenametacet (namedPieceInstrObject piece (car children) "PieceNameTacet"))
886          (header    '())
887         )
888     (if (null? music)
889       ; No staves, print tacet
890       (begin
891         (if (not-null? piecenametacet) (set! piecename piecenametacet))
892         (if (not-null? piecename)
893           (oly:add-score parser (list (oly:piece-title-markup piecename)) piecename)
894           (ly:warning (_ "No music and no score title found for part ~a and instrument ~a") piece children)
895         )
896       )
897       ; we have staves, apply the piecename to the score and add layout/midi blocks if needed
898       (begin
899         (set! score (scorify-music music parser))
900         (oly:set_piece_header score piecename)
901         (oly:apply_score_midi score)
902         (oly:apply_score_layout score)
903         ; Schedule the score for typesetting
904         (oly:add-score parser score piecename)
905       )
906     )
907   )
908   ; This is a void function, the score has been schedulled for typesetting already
909   (make-music 'Music 'void #t)
912 createVoice = #(define-music-function (parser location piece name) (string? string?)
913   (let* ((vc (oly:create_voice parser piece name)))
914     (make-music 'SimultaneousMusic
915                 'elements vc)))
917 createStaff = #(define-music-function (parser location piece name) (string? string?)
918   (oly:create_staff_or_group parser piece name))
919 createStaffForContents = #(define-music-function (parser location piece name contents) (string? string? ly:music?)
920   (let* ((tstruct (assoc-ref oly:orchestral_score_structure name))
921          (type (if (list? tstruct) (car tstruct) "Staff")))
922     (oly:staff_handler_internal parser piece name type (list contents))))
925 createScore = #(define-music-function (parser location piece children) (string? list?)
926   (oly:createScoreHelper parser location piece children keepcuefilter)
928 createNoCuesScore = #(define-music-function (parser location piece children) (string? list?)
929   (oly:createScoreHelper parser location piece children removecuefilter)
932 createHeadline = #(define-music-function (parser location headline) (string?)
933   (oly:add-toc-item parser 'tocItemMarkup headline)
934   (oly:score_handler parser (list (oly:piece-title-markup headline)))
935   (make-music 'Music 'void #t)
940 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
941 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
942 %%%%%   CUE NOTES
943 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
944 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
946 newInstrument = #(define-music-function (parser location instr) (string?)
948   \set Voice.instrumentCueName = #(string-join (list "+" instr))
951 cueText = #(define-music-function (parser location instr) (string?)
953   \set Voice.instrumentCueName = $instr
956 cueMarkup = #(define-music-function (parser location instr) (markup?)
958   \set Voice.instrumentCueName = $instr
962 clearCueText = #(define-music-function (parser location) ()
964   \unset Voice.instrumentCueName
968 insertCueText = #(define-music-function (parser location instr) (string?)
969   (if (string-null? instr)
970     #{ \tag #'cued \clearCueText #}
971     #{ \tag #'cued \cueText #instr #}
974 % generate a cue music section with instrument names
975 % Parameters: \namedCueDuring NameOfQuote CueDirection CueInstrument OriginalInstrument music
976 %                 -) NameOfQuote CueDirection music are the parameters for \cueDuring
977 %                 -) CueInstrument and OriginalInstrument are the displayed instrument names
978 % typical call:
979 % \namedCueDuring #"vIQuote" #UP #"V.I" #"Sop." { R1*3 }
980 %      This adds the notes from vIQuote (defined via \addQuote) to three measures, prints "V.I" at
981 %      the beginning of the cue notes and "Sop." at the end
982 namedCueDuring = #(define-music-function (parser location cuevoice direction instrcue instr cuemusic) (string? number? string? string? ly:music?)
984   \cueDuring #cuevoice #direction {
985     \insertCueText #instrcue
986     $cuemusic
987     \insertCueText #instr
988   }
991 namedTransposedCueDuring = #(define-music-function (parser location cuevoice direction instrcue instr trans cuemusic) (string? number? string? string? ly:music? ly:music?)
992    #{
993      \transposedCueDuring #cuevoice #direction #trans {
994        \insertCueText #instrcue
995        #cuemusic
996        \insertCueText #instr
997      }
998    #}
1001 % set the cue instrument name and clef
1002 setClefCue = #(define-music-function (parser location instr clef)
1003                                                      (string? ly:music?)
1004    #{
1005      \once \override Staff.Clef #'font-size = #-3 #clef
1006      \insertCueText #instr
1007    #} )
1009 % generate a cue music section with instrument names and clef changes
1010 % Parameters: \cleffedCueDuring NameOfQuote CueDirection CueInstrument CueClef OriginalInstrument OriginalClef music
1011 %                 -) NameOfQuote CueDirection music are the parameters for \cueDuring
1012 %                 -) CueInstrument and OriginalInstrument are the displayed instrument names
1013 %                 -) CueClef and OriginalClef are the clefs for the the cue notes and the clef of the containing voice
1014 % typical call:
1015 % \cleffedCueDuring #"vIQuote" #UP #"V.I" #"treble" #"Basso" #"bass" { R1*3 }
1016 %      This adds the notes from vIQuote (defined via \addQuote) to three measures, prints "V.I" at
1017 %      the beginning of the cue notes and "Basso" at the end. The clef is changed to treble at the
1018 %      beginning of the cue notes and reset to bass at the end
1019 cleffedCueDuring = #(define-music-function (parser location cuevoice direction instrcue clefcue instr clefinstr cuemusic)
1020                                                         (string? number? string? ly:music? string? ly:music? ly:music?)
1021    #{
1022      \cueDuring #cuevoice #direction {
1023        \tag #'cued \setClefCue #instrcue #clefcue
1024        #cuemusic
1025        \tag #'cued \setClefCue #instr #clefinstr
1026      }
1027    #}
1029 % generate a cue music section with instrument names and clef changes
1030 % Parameters: \namedCueDuringClef NameOfQuote CueDirection CueInstrument CueClef OriginalInstrument music
1031 %                 -) NameOfQuote CueDirection music are the parameters for \cueDuring
1032 %                 -) CueInstrument and OriginalInstrument are the displayed instrument names
1033 %                 -) CueClef is the clef for the the cue notes
1034 % typical call:
1035 % \namedCueDuringClef #"vIQuote" #UP #"V.I" #"treble" #"Basso" { R1*3 }
1036 %      This adds the notes from vIQuote (defined via \addQuote) to three measures, prints "V.I" at
1037 %      the beginning of the cue notes and "Basso" at the end. The clef is changed to treble at the
1038 %      beginning of the cue notes and reset to bass at the end
1039 namedCueDuringWithClef = #(define-music-function (parser location cuevoice direction instrcue clefcue instr cuemusic)
1040                                              (string? number? string? string? string? ly:music?)
1041    #{
1042      \cueDuringWithClef #cuevoice #direction #clefcue {
1043        \insertCueText #instrcue
1044        #cuemusic
1045        \insertCueText #instr
1046      }
1047    #}
1052 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1053 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1054 %%%%%   DYNAMICS
1055 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1056 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1059 dynamicsX = #(define-music-function (parser location offset) (number?)
1061     \once \override DynamicText #'X-offset = $offset
1062     \once \override DynamicLineSpanner #'Y-offset = #0
1065 % Move the dynamic sign inside the staff to a fixed staff-relative position
1066 % posY (where 0 means vertically starts at the middle staff line)
1067 dynamicsAllInside = #(define-music-function (parser location offsetX posY)
1068 (number? number?)
1070   % Invalid y-extent -> hidden from skyline calculation and collisions
1071 %   \once \override DynamicLineSpanner #'Y-extent = #(cons +0 -0.01)
1072   \once \override DynamicLineSpanner #'Y-extent = $(lambda (grob)
1073     (let* ((ext (ly:axis-group-interface::height grob))
1074            (dir (ly:grob-property grob 'direction)))
1075       (if (eq? dir UP)
1076             (cons (- (cdr ext) 0.1) (cdr ext))
1077             (cons (car ext)         (+ (car ext) 0.1)))))
1078   % move by X offset and to fixed Y-position (use Y-offset of parent!)
1079   \once \override DynamicText #'X-offset = $offsetX
1080   \once \override DynamicText #'Y-offset =
1081     $(lambda (grob)
1082        (let* ((head (ly:grob-parent grob Y))
1083               (offset (ly:grob-property head 'Y-offset)))
1084          (- posY  offset (- 0.6))))
1085   \once \override DynamicLineSpanner #'Y-offset = $posY
1088 dynamicsUpInside = #(define-music-function (parser location offsetX) (number?)
1089   ((ly:music-function-extract dynamicsAllInside) parser location offsetX 1.5)
1092 dynamicsDownInside = #(define-music-function (parser location offsetX) (number?)
1093   ((ly:music-function-extract dynamicsAllInside) parser location offsetX -3.5)
1096 hairpinOffset = #(define-music-function (parser location posY) (number?)
1098   \once \override DynamicLineSpanner #'Y-offset = $posY
1099   \once \override DynamicLineSpanner #'Y-extent = #(cons +0 -0.01)
1102 #(define ((line-break-offset before after) grob)
1103   (let* ((orig (ly:grob-original grob))
1104          ; All siblings if line-broken:
1105          (siblings (if (ly:grob? orig) (ly:spanner-broken-into orig) '() )))
1106     (if (>= (length siblings) 2)
1107       ; We have been line-broken
1108       (if (eq? (car (last-pair siblings)) grob)
1109         ; Last sibling:
1110         (ly:grob-set-property! grob 'Y-offset after)
1111         ; Others get the before value:
1112         (ly:grob-set-property! grob 'Y-offset before)
1113       )
1114     )
1115   )
1118 ffz = #(make-dynamic-script "ffz")
1119 pf = #(make-dynamic-script "pf")
1120 sempp = #(make-dynamic-script (markup #:line( #:with-dimensions '(0 . 0)
1121 '(0 . 0) #:right-align #:normal-text #:italic "sempre" #:dynamic "pp")))
1122 parenf = #(make-dynamic-script (markup #:line(#:normal-text #:italic #:fontsize 2 "(" #:dynamic "f" #:normal-text #:italic #:fontsize 2 ")")))
1123 parenp = #(make-dynamic-script (markup #:line(#:normal-text #:italic #:fontsize 2 "(" #:dynamic "p" #:normal-text #:italic #:fontsize 2 ")")))
1124 pdolce = #(make-dynamic-script (markup #:line(#:dynamic "p" #:with-dimensions '(0 . 0) '(0 . 0) #:normal-text #:italic "dolce")))
1125 ppdolce = #(make-dynamic-script (markup #:line(#:dynamic "pp" #:with-dimensions '(0 . 0) '(0 . 0) #:normal-text #:italic "dolce")))
1126 dolce = #(make-dynamic-script (markup #:line(#:normal-text #:italic "dolce")))
1127 sfpdolce = #(make-dynamic-script (markup #:line(#:dynamic "sfp" #:with-dimensions '(0 . 0) '(0 . 0) #:normal-text #:italic "dolce"  )))
1128 bracketf = #(make-dynamic-script (markup #:line(#:concat(#:normal-text #:fontsize 3 "[" #:dynamic "f" #:hspace 0.1 #:normal-text #:fontsize 3 "]"))))
1129 bracketmf = #(make-dynamic-script (markup #:line(#:concat(#:normal-text #:fontsize 3 "[" #:dynamic "mf" #:hspace 0.1 #:normal-text #:fontsize 3 "]"))))
1130 bracketmp = #(make-dynamic-script (markup #:line(#:concat(#:normal-text #:fontsize 2 "[" #:hspace 0.2 #:dynamic "mp" #:normal-text #:fontsize 2 "]"))))
1131 bracketp = #(make-dynamic-script (markup #:line(#:concat(#:normal-text #:fontsize 2 "[" #:hspace 0.2 #:dynamic "p" #:normal-text #:fontsize 2 "]"))))
1133 whiteoutp = #(make-dynamic-script (markup #:whiteout #:pad-markup 0.5 #:dynamic "p"))
1134 whiteoutf = #(make-dynamic-script (markup #:whiteout #:pad-markup 0.5 #:dynamic "f"))
1135 whiteoutff = #(make-dynamic-script (markup #:whiteout #:pad-markup 0.5 #:dynamic "ff"))
1138 cresc = #(make-music 'CrescendoEvent 'span-direction START
1139                      'span-type 'text 'span-text "cresc.")
1140 dim = #(make-music 'DecrescendoEvent 'span-direction START
1141                    'span-type 'text 'span-text "dim.")
1142 decresc = #(make-music 'DecrescendoEvent 'span-direction START
1143                        'span-type 'text 'span-text "decresc.")
1147 %%% Thanks to "Gilles THIBAULT" <gilles.thibault@free.fr>, there is a way
1148 %   to remove also the fermata from R1-\fermataMarkup: By filtering the music
1149 %   and removing the corresponding events.
1150 %   Documented as an LSR snippet: http://lsr.dsi.unimi.it/LSR/Item?id=372
1151 #(define (filterOneEventsMarkup event)
1152 ( let ( (eventname (ly:music-property  event 'name)) )
1153  (not
1154   (or     ;; add here event name you do NOT want
1155    (eq? eventname 'MultiMeasureTextEvent)
1156    (eq? eventname 'AbsoluteDynamicEvent)
1157    (eq? eventname 'TextScriptEvent)
1158    (eq? eventname 'ArticulationEvent)
1159    (eq? eventname 'CrescendoEvent)
1160    (eq? eventname 'DecrescendoEvent)
1161   )
1165 filterArticulations = #(define-music-function (parser location music) (ly:music?)
1166   (music-filter filterOneEventsMarkup music)
1171 %%% Add the same articulation to a longer sequence of notes:
1172 #(define (make-script x)
1173    (make-music 'ArticulationEvent
1174                'articulation-type x))
1176 #(define (add-articulation music art)
1177    (map-some-music
1178      (lambda (m)
1179        (cond ((music-is-of-type? m 'event-chord)
1180                 (set! (ly:music-property m 'elements)
1181                         (append (ly:music-property m 'elements)
1182                           (list (make-script art))))
1183                 m)
1184              ((music-is-of-type? m 'note-event)
1185                 (set! (ly:music-property m 'articulations)
1186                         (append (ly:music-property m 'articulations)
1187                           (list (make-script art))))
1188                 m)
1189              (else #f)))
1190       music))
1192 addArticulation = #(define-music-function (parser location type music) 
1193                                           (string? ly:music? )
1194                 (add-articulation music type))
1199 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1200 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1201 %%%%%   Tempo markings
1202 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1203 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1207 rit = \markup {\italic "rit."}
1208 atempo = \markup {\italic "a tempo"}
1209 pocorit = \markup {\italic "poco rit."}
1210 ppmosso = \markup {\italic "poco più mosso"}
1211 pizz = \markup {\italic "pizz."}
1212 arco = \markup {\italic "arco"}
1213 colarco = \markup {\italic "Col' arco"}
1214 perd = \markup {\italic "perdend."}
1219 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1220 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1221 %%%%%   REST COMBINATION
1222 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1223 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1227 %% REST COMBINING, TAKEN FROM http://lsr.dsi.unimi.it/LSR/Item?id=336
1229 %% Usage:
1230 %%   \new Staff \with {
1231 %%     \override RestCollision #'positioning-done = #merge-rests-on-positioning
1232 %%   } << \somevoice \\ \othervoice >>
1233 %% or (globally):
1234 %%   \layout {
1235 %%     \context {
1236 %%       \Staff
1237 %%       \override RestCollision #'positioning-done = #merge-rests-on-positioning
1238 %%     }
1239 %%   }
1241 %% Limitations:
1242 %% - only handles two voices
1243 %% - does not handle multi-measure/whole-measure rests
1245 #(define (rest-score r)
1246   (let ((score 0)
1247   (yoff (ly:grob-property-data r 'Y-offset))
1248   (sp (ly:grob-property-data r 'staff-position)))
1249     (if (number? yoff)
1250   (set! score (+ score 2))
1251   (if (eq? yoff 'calculation-in-progress)
1252       (set! score (- score 3))))
1253     (and (number? sp)
1254    (<= 0 2 sp)
1255    (set! score (+ score 2))
1256    (set! score (- score (abs (- 1 sp)))))
1257     score))
1259 #(define (merge-rests-on-positioning grob)
1260   (let* ((can-merge #f)
1261    (elts (ly:grob-object grob 'elements))
1262    (num-elts (and (ly:grob-array? elts)
1263       (ly:grob-array-length elts)))
1264    (two-voice? (= num-elts 2)))
1265     (if two-voice?
1266   (let* ((v1-grob (ly:grob-array-ref elts 0))
1267          (v2-grob (ly:grob-array-ref elts 1))
1268          (v1-rest (ly:grob-object v1-grob 'rest))
1269          (v2-rest (ly:grob-object v2-grob 'rest)))
1270     (and
1271      (ly:grob? v1-rest)
1272      (ly:grob? v2-rest)
1273      (let* ((v1-duration-log (ly:grob-property v1-rest 'duration-log))
1274       (v2-duration-log (ly:grob-property v2-rest 'duration-log))
1275       (v1-dot (ly:grob-object v1-rest 'dot))
1276       (v2-dot (ly:grob-object v2-rest 'dot))
1277       (v1-dot-count (and (ly:grob? v1-dot)
1278              (ly:grob-property v1-dot 'dot-count -1)))
1279       (v2-dot-count (and (ly:grob? v2-dot)
1280              (ly:grob-property v2-dot 'dot-count -1))))
1281        (set! can-merge
1282        (and
1283         (number? v1-duration-log)
1284         (number? v2-duration-log)
1285         (= v1-duration-log v2-duration-log)
1286         (eq? v1-dot-count v2-dot-count)))
1287        (if can-merge
1288      ;; keep the rest that looks best:
1289      (let* ((keep-v1? (>= (rest-score v1-rest)
1290               (rest-score v2-rest)))
1291       (rest-to-keep (if keep-v1? v1-rest v2-rest))
1292       (dot-to-kill (if keep-v1? v2-dot v1-dot)))
1293        ;; uncomment if you're curious of which rest was chosen:
1294        ;;(ly:grob-set-property! v1-rest 'color green)
1295        ;;(ly:grob-set-property! v2-rest 'color blue)
1296        (ly:grob-suicide! (if keep-v1? v2-rest v1-rest))
1297        (if (ly:grob? dot-to-kill)
1298            (ly:grob-suicide! dot-to-kill))
1299        (ly:grob-set-property! rest-to-keep 'direction 0)
1300        (ly:rest::y-offset-callback rest-to-keep)))))))
1301     (if can-merge
1302   #t
1303   (ly:rest-collision::calc-positioning-done grob))))
1309 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1310 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1311 %%%%%   TABLE OF CONTENTS
1312 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1313 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1316 contentsTitle = "Inhalt / Contents"
1318 \paper {
1319   tocTitleMarkup = \markup \fill-line{
1320     \null
1321     \column {
1322       \override #(cons 'line-width (* 7 cm))
1323       \line{ \fill-line {\piece-title {\contentsTitle} \null }}
1324       \hspace #1
1325     }
1326     \null
1327   }
1328   tocItemMarkup = \markup \fill-line {
1329     \null
1330     \column {
1331       \override #(cons 'line-width (* 7 cm ))
1332       \line { \fill-line{\fromproperty #'toc:text \fromproperty #'toc:page }}
1333     }
1334     \null
1335   }
1339 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1340 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1341 %%%%%   TITLE PAGE / HEADER
1342 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1343 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1345 #(define-markup-command (when-property layout props symbol markp) (symbol? markup?)
1346   (if (chain-assoc-get symbol props)
1347       (interpret-markup layout props markp)
1348       (ly:make-stencil '()  '(1 . -1) '(1 . -1))))
1350 #(define-markup-command (vspace layout props amount) (number?)
1351   "This produces a invisible object taking vertical space."
1352   (let ((amount (* amount 3.0)))
1353     (if (> amount 0)
1354         (ly:make-stencil "" (cons -1 1) (cons 0 amount))
1355         (ly:make-stencil "" (cons -1 1) (cons amount amount)))))
1359 titlePageMarkup = \markup \abs-fontsize #10 \when-property #'header:title \column {
1360     \vspace #4
1361     \fill-line { \fontsize #8 \fromproperty #'header:composer }
1362     \vspace #1
1363     \fill-line { \fontsize #8 \fromproperty #'header:poet }
1364     \vspace #4
1365     \fill-line { \fontsize #10 \bold \fromproperty #'header:titlepagetitle }
1366     \vspace #1
1367     \fontsize #2 \when-property #'header:titlepagesubtitle {
1368       \fill-line { \fromproperty #'header:titlepagesubtitle }
1369       \vspace #1
1370     }
1371     \fill-line { \postscript #"-20 0 moveto 40 0 rlineto stroke" }
1372     \vspace #8
1373     \fill-line { \fontsize #5 \fromproperty #'header:ensemble }
1374     \vspace #0.02
1375     \fill-line { \fontsize #2 \fromproperty #'header:instruments }
1376     \vspace #9
1377     \fill-line { \fontsize #5 \fromproperty #'header:date }
1378     \vspace #1
1379     \fill-line { \fontsize #5 \fromproperty #'header:scoretype }
1380     \vspace #1
1381     \when-property #'header:instrument {
1382       \fill-line { \bold \fontsize #6 \rounded-box \fromproperty #'header:instrument }
1383     }
1384     \vspace #7
1385     \fontsize #2 \when-property #'header:enteredby \override #'(baseline-skip . 3.75) \left-align\center-column {
1386       \fill-line { "Herausgegeben von: / Edited by:"}
1387       \vspace #0.
1388       \fill-line { \fromproperty #'header:enteredby }
1389     }
1390     \fill-line {
1391       \when-property #'header:arrangement \column {
1392         \vspace #8
1393         \fill-line { \fontsize #3 \fromproperty #'header:arrangement }
1394       }
1395     }
1396   \vspace #6
1397   \fill-line { \fromproperty #'header:copyright }
1400 titleHeaderMarkup = \markup {
1401   \override #'(baseline-skip . 3.5)
1402   \column {
1403     \fill-line {
1404       \fromproperty #'header:logo
1405       \override #'(baseline-skip . 4.5) \center-column {
1406         \bold \abs-fontsize #18 \fromproperty #'header:title
1407         \bold \abs-fontsize #12 \fromproperty #'header:subtitle
1408         \abs-fontsize #11 \fromproperty #'header:subsubtitle
1409       }
1410       \bold \abs-fontsize #11 \when-property #'header:instrument \rounded-box \fromproperty #'header:instrument
1411     }
1412     \fill-line {
1413       \with-dimensions #'( 0 . 0) #'( 0 . 1 ) \null
1414     }
1416     \fill-line {
1417             \abs-fontsize #10 \fromproperty #'header:poet
1418             \abs-fontsize #10 \fromproperty #'header:composer
1419     }
1420     \fill-line {
1421             \abs-fontsize #10 \fromproperty #'header:meter
1422             \abs-fontsize #10 \fromproperty #'header:arranger
1423     }
1424   }
1426 date = #(strftime "%d-%m-%Y" (localtime (current-time)))
1427 \header {
1428   logo = \date
1432 titleScoreMarkup = \markup \piece-title \fromproperty #'header:piece
1434 \paper {
1435   scoreTitleMarkup = \titleScoreMarkup
1436   bookTitleMarkup = \titleHeaderMarkup
1441 %%%%%%%%%%%%%% headers and footers %%%%%%%%%%%%%%%%%%%%%%%%%%
1443 #(define (first-score-page layout props arg)
1444   (let* ((label 'first-score-page)
1445          (table (ly:output-def-lookup layout 'label-page-table))
1446          (label-page (and (list? table) (assoc label table)))
1447          (page-number (and label-page (cdr label-page)))
1448         )
1449     (if (eq? (chain-assoc-get 'page:page-number props -1) page-number)
1450       (interpret-markup layout props arg)
1451       empty-stencil)))
1453 #(define no-header-table '(1))
1454 addNoHeaderPage = #(define-music-function (parser location nr) (number?)
1455   (set! no-header-table (cons nr no-header-table))
1456   (make-music 'Music 'void #t))
1457 setNoHeaderPages = #(define-music-function (parser location pages) (list?)
1458   (set! no-header-table pages)
1459   (make-music 'Music 'void #t))
1461 #(define (is-header-page layout props arg)
1462   (let* ((page-number (chain-assoc-get 'page:page-number props -1)))
1463     (if (not (member page-number no-header-table))
1464       (interpret-markup layout props arg)
1465       empty-stencil)))
1467 #(define no-footer-table '(1))
1468 addNoFooterPage = #(define-music-function (parser location nr) (number?)
1469   (set! no-footer-table (cons nr no-footer-table))
1470   (make-music 'Music 'void #t))
1471 setNoFooterPages = #(define-music-function (parser location pages) (list?)
1472   (set! no-footer-table pages)
1473   (make-music 'Music 'void #t))
1475 #(define (is-footer-page layout props arg)
1476   (let* ((page-number (chain-assoc-get 'page:page-number props -1)))
1477     (if (not (member page-number no-footer-table))
1478       (interpret-markup layout props arg)
1479       empty-stencil)))
1481 #(define copyright-pages-table '(1))
1482 addCopyrightPage = #(define-music-function (parser location nr) (number?)
1483   (set! copyright-pages-table (cons nr copyright-pages-table))
1484   (make-music 'Music 'void #t))
1485 setCopyrightPages = #(define-music-function (parser location pages) (list?)
1486   (set! copyright-pages-table pages)
1487   (make-music 'Music 'void #t))
1489 #(define (is-copyright-page layout props arg)
1490   (let* ((page-number (chain-assoc-get 'page:page-number props -1)))
1491     (if (member page-number copyright-pages-table)
1492       (interpret-markup layout props arg)
1493       empty-stencil)))
1497 \paper {
1498   olyStdOddHeaderMarkup = \markup \fill-line {
1499     %% force the header to take some space, otherwise the
1500     %% page layout becomes a complete mess.
1501     " "
1502     \on-the-fly #is-header-page \fromproperty #'header:title
1503     \on-the-fly #is-header-page \fromproperty #'page:page-number-string
1504   }
1505   olyStdEvenHeaderMarkup = \markup \fill-line {
1506     \on-the-fly #is-header-page \fromproperty #'page:page-number-string
1507     \on-the-fly #is-header-page \fromproperty #'header:composer
1508     " "
1509   }
1510   olyInstrumentOddHeaderMarkup = \markup \fill-line {
1511     " "
1512     \on-the-fly #is-header-page \concat { \fromproperty #'header:instrument }
1513     \on-the-fly #is-header-page \fromproperty #'page:page-number-string
1514   }
1515   olyInstrumentEvenHeaderMarkup = \markup \fill-line {
1516     \on-the-fly #is-header-page \fromproperty #'page:page-number-string
1517     \on-the-fly #is-header-page \concat { \fromproperty #'header:composer ": " \fromproperty #'header:title }
1518     " "
1519   }
1520   oddHeaderMarkup = \olyStdOddHeaderMarkup
1521   evenHeaderMarkup = \olyStdEvenHeaderMarkup
1523   olyStdOddFooterMarkup = \markup {
1524     \column {
1525       \fill-line {
1526         %% publisher header field only on title page.
1527         \on-the-fly #first-page \fromproperty #'header:publisher
1528       }
1529       \fill-line {
1530         %% copyright on the first real score page
1531         \on-the-fly #is-copyright-page \fromproperty #'header:copyright
1532         \on-the-fly #is-copyright-page \null
1533       }
1534       \fill-line {
1535         %% All other pages get the number of the edition centered
1536         \on-the-fly #is-footer-page \fromproperty #'header:scorenumber
1537       }
1538     }
1539   }
1540   olyInstrumentOddFooterMarkup = \markup {
1541     \column {
1542       \fill-line {
1543         %% copyright on the first real score page
1544         \on-the-fly #is-copyright-page \fromproperty #'header:copyright
1545         \on-the-fly #is-copyright-page \null
1546       }
1547       \fill-line {
1548         %% All other pages get the number of the edition centered
1549         \on-the-fly #is-footer-page \fromproperty #'header:scorenumber
1550       }
1551     }
1552   }
1553   oddFooterMarkup = \olyStdOddFooterMarkup
1566 % Interpret the given markup with the header fields added to the props.
1567 % This way, one can re-use the same functions (using fromproperty
1568 % #'header:field) in the header block and as top-level markup.
1570 % This function is originally copied from mark-up-title (file scm/titling.scm),
1571 % which is lilypond's internal function to handle the title markups. I needed
1572 % to replace the scopes and manually add the $defaultheader (which is internally
1573 % done in paper-book.cc before calling mark-up-title. Also, I don't extract the
1574 % markup from the header block, but use the given markup.
1576 % I'm not sure if I really need the page properties in props, too... But I
1577 % suppose it does not hurt, either.
1578 #(define-markup-command (markupWithHeader layout props markup) (markup?)
1579   "Interpret the given markup with the header fields added to the props.
1580    This way, one can re-use the same functions (using fromproperty
1581    #'header:field) in the header block and as top-level markup."
1582   (let* (
1583       ; TODO: If we are inside a score, add the score's local header block, too!
1584       ; Currently, I only use the global header block, stored in $defaultheader
1585       (scopes (list $defaultheader))
1586       (alists (map ly:module->alist scopes))
1588       (prefixed-alist
1589         (map (lambda (alist)
1590           (map (lambda (entry)
1591             (cons
1592               (string->symbol (string-append "header:" (symbol->string (car entry))))
1593               (cdr entry)))
1594             alist))
1595           alists))
1596       (props (append prefixed-alist
1597               props
1598               (layout-extract-page-properties layout)))
1599     )
1600     (interpret-markup layout props markup)
1601   )
1609 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1610 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1611 %%%%%   Equally spacing multiple columns (e.g. for translations)
1612 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1613 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1615 % Credits: Nicolas Sceaux on the lilypond-user mailinglist
1616 #(define-markup-command (columns layout props args) (markup-list?)
1617    (let ((line-width (/ (chain-assoc-get 'line-width props
1618                          (ly:output-def-lookup layout 'line-width))
1619                         (max (length args) 1))))
1620      (interpret-markup layout props
1621        (make-line-markup (map (lambda (line)
1622                                 (markup #:pad-to-box `(0 . ,line-width) '(0 . 0)
1623                                   #:override `(line-width . ,line-width)
1624                                   line))
1625                                args)))))
1629 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1630 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1631 %%%%%   SCORE (HEADER / LAYOUT) SETTINGS
1632 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1633 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1636 startSlashedGraceMusic =  {
1637   \override Flag #'stroke-style = #"grace"
1640 stopSlashedGraceMusic =  {
1641   \revert Flag #'stroke-style
1644 slashedGrace =
1645 #(def-grace-function startSlashedGraceMusic stopSlashedGraceMusic
1646    (_i "Create slashed graces (slashes through stems, but no slur)from the following music expression"))
1649 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1650 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1651 %%%%%   SCORE (HEADER / LAYOUT) SETTINGS
1652 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1653 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1655 \paper {
1656   footnote-separator-markup = \markup { \fill-line { \override #`(span-factor . 1/4) { \draw-hline } \null }}
1658   left-margin = 2\cm
1659   right-margin = 1.5\cm
1660   line-width = 17.5\cm
1661 %   bottom-margin = 1.5\cm
1662   top-margin = 0.7\cm
1663   ragged-right = ##f
1664   ragged-last = ##f
1665   ragged-bottom = ##f
1666   ragged-last-bottom = ##f
1668 \layout {
1669   \context {
1670     \ChoirStaff
1671     % If only one non-empty staff in a system exists, still print the backet
1672     \override SystemStartBracket #'collapse-height = #1
1673     \consists "Instrument_name_engraver"
1674     \consists "Keep_alive_together_engraver"
1675   }
1676   \context {
1677     \StaffGroup
1678     % If only one non-empty staff in a system exists, still print the backet
1679     \override SystemStartBracket #'collapse-height = #1
1680     \consists "Instrument_name_engraver"
1681   }
1682   \context {
1683     \GrandStaff
1684     \override SystemStartBracket #'collapse-height = #1
1685     \consists "Instrument_name_engraver"
1686   }
1687   \context {
1688     \FiguredBass
1689     \override VerticalAxisGroup #'padding = #0
1690   }
1691   \context {
1692     \Score
1693     % Force multi-measure rests to be written as one span
1694     \override MultiMeasureRest #'expand-limit = #3
1695     skipBars = ##t
1696     autoBeaming = ##f
1697     \override CombineTextScript #'avoid-slur = #'outside
1698     \override DynamicTextSpanner #'style = #'none
1699     \override InstrumentSwitch #'font-size = #-1
1701     % Rest collision
1702     \override RestCollision #'positioning-done = #merge-rests-on-positioning
1703     % Auto-Accidentals: Use modern-cautionary style...
1704     extraNatural = ##f
1705     % Accidental rules (the rule giving the most accidentals wins!)
1706     % -) Reset accidentals at each barline -> accs not in key sig will always be printed
1707     % -) Same octave accidentals are remembered for two measures -> cancellation
1708     % -) other octave accidentals are remembered for next measure -> cancellation
1709     autoAccidentals = #`(Staff  ,(make-accidental-rule 'same-octave 0)
1710                                 ,(make-accidental-rule 'any-octave 0)
1711                                 ,(make-accidental-rule 'any-octave 1)
1712                                 ,(make-accidental-rule 'same-octave 2))
1713     % No auto-cautionaries, we always use autoAccidentals!
1714 %     autoCautionaries = #`(Staff ,(make-accidental-rule 'any-octave 0)
1715 %                                 ,(make-accidental-rule 'same-octave 1))
1716     printKeyCancellation = ##t
1717     quotedEventTypes = #'(StreamEvent)
1718     quotedCueEventTypes = #'(
1719       rhythmic-event
1720       tie-event
1721       beam-event
1722       tuplet-span-event
1723       tremolo-event
1724       glissando-event
1725       harmonic-event
1726       repeat-tie-event
1727       articulation-event
1728       slur-event
1729       trill-span-event
1730       tremolo-span-event
1731     )
1732     implicitBassFigures = #'(0 100)
1733   }
1734   \context {
1735     \Staff
1736     \RemoveEmptyStaves
1737   }
1741 ts = #(make-music 'TextScriptEvent 'text "t.s." 'direction UP )
1742 tt = #(make-music 'TextScriptEvent 'text "Tutti" 'direction UP )
1743 solo = #(make-music 'TextScriptEvent 'text "Solo" 'direction UP )
1744 tutti = #(make-music 'TextScriptEvent 'text "Tutti" 'direction UP )
1745 bracketts = #(make-music 'TextScriptEvent 'text "[t.s.]" 'direction UP )
1746 brackettt = #(make-music 'TextScriptEvent 'text "[Tutti]" 'direction UP )
1747 bracketsolo = #(make-music 'TextScriptEvent 'text "[Solo]" 'direction UP )
1749 sottovoce = #(make-music 'TextScriptEvent 'text "sotto voce" 'direction UP )
1751 dashedSlur = -\tweak #'dash-definition #'((0 1 0.4 0.75))(
1752 dashedTie = -\tweak #'dash-definition #'((0 1 0.4 0.75))~
1754 divisi = #(define-music-function (parser location vc1 vc2) (ly:music? ly:music?)
1756   << { \voiceOne $vc1 \oneVoice} \context Voice = "divisi2" { \voiceTwo $vc2 } >>
1760 #(define twoVoice divisi)
1762 #(define-public (bracket-stencils grob)
1763   (let ((lp (grob-interpret-markup grob (markup #:fontsize 3.5 #:translate (cons -0.3 -0.5) "[")))
1764         (rp (grob-interpret-markup grob (markup #:fontsize 3.5 #:translate (cons -0.3 -0.5) "]"))))
1765     (list lp rp)))
1767 bracketify = #(define-music-function (parser loc arg) (ly:music?)
1768    (_i "Tag @var{arg} to be parenthesized.")
1770   \once \override ParenthesesItem #'stencils = #bracket-stencils
1771   \parenthesize $arg
1776 #(define-markup-command (hat layout props arg) (markup?)
1777   "Draw a hat above the given string @var{arg}."
1778   (interpret-markup layout props (markup #:combine #:raise 1.5 "^" arg)))
1782 smallFlageolet =
1783 #(let ((m (make-music 'ArticulationEvent
1784                       'articulation-type "flageolet")))
1785    (ly:music-set-property! m 'tweaks
1786      (acons 'font-size -2
1787        (ly:music-property m 'tweaks)))
1788   m)
1791 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1792 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1793 %%%%%   LICENSE TEXTS
1794 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1795 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1797 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" }}
1798 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" }}
1799 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" }}
1800 LicenseNoRestrictions = \markup{\line {Die Ausgabe darf kopiert und ohne Einschränkungen aufgeführt werden. / May be copied and performed without restriction.}}
1802 \include "sceaux_clef-key.ily"
1805 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1806 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1807 %%%%%   VARIOUS
1808 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1809 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1811 startUnremovableSection = \set Staff.keepAliveInterfaces =
1812  #'(rhythmic-grob-interface
1813     rest-interface
1814     lyric-interface
1815     percent-repeat-item-interface
1816     percent-repeat-interface
1817     stanza-number-interface)
1819 endUnremovableSection = \unset Staff.keepAliveInterfaces
1822 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1823 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1824 %%%%%   EDITORIAL ANNOTATIONS
1825 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1826 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1828 #(define-public (editorial-bracket-stencil stil padding widen)
1829 "Add brackets for editorial annoations around STIL, producing a new stencil."
1830 (let* ((axis Y)
1831        (other-axis (lambda (a) (remainder (+ a 1) 2)))
1832        (ext (interval-widen (ly:stencil-extent stil axis) widen))
1833        (thick 0.15)
1834        (protrusion 0.3)
1835        (lb (ly:bracket axis ext thick protrusion))
1836        (rb (ly:bracket axis ext thick (- protrusion))))
1837   (set! stil (ly:stencil-combine-at-edge stil (other-axis axis) 1 rb padding))
1838   (set! stil
1839     (ly:stencil-combine-at-edge lb (other-axis axis) 1 stil padding))
1840   stil))
1842 editorialHairpin = \once \override Hairpin     #'stencil = #(lambda (grob) (editorial-bracket-stencil (ly:hairpin::print grob) 0.2 0.55))
1843 editorialDynamic = \once \override DynamicText #'stencil = #(lambda (grob) (editorial-bracket-stencil (ly:text-interface::print grob) 0.2 0.55))
1844 editorialMarkup =  \once \override TextScript  #'stencil = #(lambda (grob) (editorial-bracket-stencil (ly:text-interface::print grob) 0.2 0.55))
1846 % videStart = \mark \markup { \hspace #1 \musicglyph #"scripts.coda"  \with-dimensions #'(0 . 0) #'(0 . 0) \left-align { vi-} }
1847 videStart = \mark \markup \halign #-2.3 \concat { \hspace #4.5 \musicglyph #"scripts.coda" \left-align { vi- } }
1848 % videEnd = \notemode {
1849 %   \once \override Score.RehearsalMark #'break-visibility = #begin-of-line-invisible
1850 %   \mark \markup \concat{ \with-dimensions #'(0 . 0) #'(0 . 0) \right-align { -de } \hspace #1 \musicglyph #"scripts.coda" }
1852 videEnd = \notemode {
1853         \once \override Score.RehearsalMark #'break-visibility = #begin-of-line-invisible
1854         \mark \markup \concat{ \right-align { -de } \hspace #1.5 \musicglyph #"scripts.coda" \hspace #4.2 }
1859 \layout {
1860         \context {\Staff
1861                 soloText = #"I"
1862                 soloIIText = #"II"
1863                 aDueText = #"a2"
1864         }
1867 \paper {
1868 %   annotate-spacing = ##t
1869   ragged-bottom = ##f
1870   ragged-last = ##f
1871   ragged-last-bottom = ##f
1873   top-markup-spacing #'minimum-distance = #5
1874 %   top-markup-spacing #'basic-distance = #4
1875 %   top-markup-spacing #'padding = #2
1876   top-markup-spacing #'stretchability = #15
1878   top-system-spacing #'minimum-distance = #0
1879 %   top-system-spacing #'basic-distance = #3
1880   top-system-spacing #'padding = #2
1881   top-system-spacing #'stretchability = #13
1882   
1883   markup-system-spacing #'minimum-distance = #5
1884 %   markup-system-spacing #'basic-distance = #4
1885   markup-system-spacing #'padding = #3
1886   markup-system-spacing #'stretchability = #25
1887   
1888   system-system-spacing #'minimum-distance = #0
1889 %   system-system-spacing #'basic-distance = #5
1890   system-system-spacing #'padding = #2
1891   system-system-spacing #'stretchability = #15
1892   
1893   last-bottom-spacing #'basic-distance = #3
1894 %   last-bottom-spacing #'basic-distance = #7
1895   last-bottom-spacing #'padding = #4
1896   last-bottom-spacing #'stretchability = #14
1898 %   score-markup-spacing #'basic-distance = #5
1899 %   score-markup-spacing #'stretchability = #15
1901 %   markup-markup-spacing #'basic-distance = #5
1902 %   markup-markup-spacing #'stretchability = #30
1905 \layout {
1906   \context { \PianoStaff
1907     \override StaffGrouper #'staff-staff-spacing #'stretchability = #1.5
1908   }
1909   \context { \StaffGroup
1910     \override StaffGrouper #'staff-staff-spacing #'stretchability = #2.5
1911     \override SystemStartBracket #'collapse-height = #1
1912   }
1913   \context { \GrandStaff
1914     \override StaffGrouper #'staff-staff-spacing #'stretchability = #3
1915     \override StaffGrouper #'staffgroup-staff-spacing #'stretchability = #3
1916    }
1917   \context { \ChoirStaff
1918     \override StaffGrouper #'staff-staff-spacing #'stretchability = #1
1919   }
1920   \context { \Staff
1921     \override StaffGrouper #'staff-staff-spacing #'stretchability = #4.9
1922   }
1923   \context { \Score
1924     \override StaffGrouper #'staff-staff-spacing #'stretchability = #5
1925   }
1930 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1931 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1932 %%%%%   WORKAROUNDS!
1933 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1934 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1936 % _ does not work as a direction modifier in figured bass
1937 tsdown = #(make-music 'TextScriptEvent 'text "t.s." 'direction DOWN )