The translation process#

Overview#

Translation in LilyPond is the flow of making a graphical representation of music. It is the stage where timing information is determined. During translation, grobs are created, and they set up for processing by the backend, including parents, bounds and pointers.

Translation happens through several kinds of objects.

Contexts are used to store data. They are typed, and correspond to a certain portion of the score, vertically. They are created following a hierarchy. Common context types include Score, StaffGroup, Staff and Voice. All contexts types are listed in the Internals Reference under Contexts.

Stream events are derivatives of music events. They have a different class in C++ and a different Scheme type predicate: ly:stream-event?. Most music event types are turned into stream events when their time comes. This does not hold for music types that contain other music events, such as SequentialMusic. As a rule of thumb, music types ending in Event are slated to become stream events, such as NoteEvent, RestEvent, AbsoluteDynamicEvent, to name a few.

Events are Probs, hence the functions related to event properties: ly:event-property and ly:event-set-property!.

Iterators are responsible for the timing. They advance in „container“ music expressions – those preferably ending in Music rather than Event – and broadcast their contents as stream events or create child iterators for nested container expressions.

Engravers react to the stream events broadcast from iterators. They can create grobs, read and set context properties, and process the grobs created by other engravers. Overall, they constitute the main component of translation. There is an engraver for every single bit of notation: Note_heads_engraver, Stem_engraver, Beam_engraver, Staff_symbol_engraver, and many others. In contrast to iterators, it is possible to write engravers in Scheme.

Engravers have no properties, because they are generally not directly used as objects. They communicate through context properties.

By convention, iterator and engraver names are written Capitalized_with_underscores. Stream events do not have any particular type. They are based on event classes rather than music types. Event classes are rather similar to music classes, but separate, though generally about the same.

Contexts#

Context properties#

Contexts contain properties. In LilyPond syntax, the standard way to modify properties of a context is the \set command:

\set [ContextName.]propertyName = value

Behind the scenes, this inserts a PropertySet event in the music. When iterated, this event causes the property to be set (through the Property_iterator).

Contexts are Probs, with the associated functions:

(ly:context-property context property [default])
(ly:context-set-property! context property value)

Moreover, every context contains grob property settings. The command to change them in the music is \override:

\override [ContextName.]GrobName.property-name = value

In Scheme, the following functions deal with grob property defaults:

(ly:context-grob-definition context grob)

Return an alist mapping property names (as symbols) to their defaults for the grob (a symbol) in context.

(ly:context-pushpop-property context grob property [value])

If value is given, push it as a default for grob.property in context. This is the equivalent of a \temporary \override.

Without a value, pop the top of the stack. This is like \revert.

Note that for backwards compatibility reasons, \override without \temporary pops the stack before pushing. This means that after a sequence of \override commands, \revert does not reinstate the value before the last \override but the primary, global default value for the grob property in the context type.

The context hierarchy#

Context follow a hierarchical structure. The top-most context is called Global. Every context but Global is contained in a parent. Typically, the parent of a Voice context is a Staff context, and the parent of a Staff context is a Score context. A staff could also be contained in a StaffGroup context or another kind of staff container (such as PianoStaff, GrandStaff or ChoirStaff).

(ly:context-parent context)

Return the parent of context, or #f if context is the Global context.

(ly:context-find context name)

Search and return a context with the given name (a symbol) above context: its parent, or the parent of its parent, or …

Return the boolean false if no appropriate parent is found.

Aliases are a way for the more rarely used context types, like TabStaff, to fit in the hierarchy of the more frequently used, such as Staff. Contexts having the name as alias are also considered by ly:context-find. Thus, a TabStaff may be found as a Staff parent to a TabVoice. This allows engravers to work in several context types.

Context IDs#

Every context is known under an ID, accessible through the function ly:context-id. The syntax \new Staff = "up" ... sets this ID. By default, it is generated automatically.

Beware, IDs do not identify contexts uniquely. For example, this works:

\version "2.25.8"

<<
  \new PianoStaff <<
    \new Staff = "up" { c'8 8 \change Staff = "down" 8 8 }
    \new Staff = "down" { s8 s s s }
  >>
  \new PianoStaff <<
    \new Staff = "up" { c'8 8 \change Staff = "down" 8 8 }
    \new Staff = "down" { s8 s s s }
  >>
>>
Output../../images/4c57d8f8c0969cf40b12b2a6c45fa4aff832c668ba5bf2d3eb0e6a38088813bd.svg

Defining new context types#

The official documentation has excellent details on Defining new contexts.

Useful translation hooks#

The sledgehammer for doing about anything you want during the translation step is writing an engraver. However, it can also be quite heavyweight. Before diving into engravers, it is useful to learn about a few simpler programming interfaces.

Accessing a context#

In the course of a music expression, the \applyContext command can be used to apply a certain function to a context. This comes in handy when the settings that are to be applied to the context depend on its properties. The \applyContext function takes a single parameter, a function taking a context argument. It applies in the context the music expression is being iterated in. To specify a different context, the \context command should be used. It sends music to a context found above the current one by type.

For example, here is how to increment the bar number by one:

\version "2.25.8"

incrementBar =
\context Score
  \applyContext
    #(lambda (context)
       (ly:context-set-property!
         context
         'currentBarNumber
         (1+ (ly:context-property context 'currentBarNumber))))

{
  c'1\break
  c'1\break
  \incrementBar
  c'1
}
Output../../images/b31ec38cca9cad4e8b56e6f5279cd05251b12090a6faaa3187340194a7220319.svg

Tweaking grobs during translation#

A later section examines methods to change the appearance and positioning of grobs in the backend. The \applyOutput command is a facility to apply a function to certain grobs created in a context or any of its descendants, at a single moment. It is useful for local tweaks depending on context settings. There are two forms for \applyOutput:

\applyOutput Context #procedure
\applyOutput Context.Grob #procedure

In the latter form, grobs of the specified types are matched, while in the former, all grobs match.

The procedure is called with three arguments:

  • The grob,

  • The context it originates from,

  • The context \applyOutput applies to.

A motivating use case is to set the color for all grobs:

\version "2.25.8"

colorNotes =
#(define-music-function (color) (color?)
   #{
     \applyOutput Voice
       #(lambda (grob origin-context context)
          (ly:grob-set-property! grob 'color color))
   #})

{
  \colorNotes red
  <e' g' bes'>4
  <e' g' a'>4
  \colorNotes green
  <d' fis' a'>4
}
Output../../images/783107af5d9713bce9b9eac3831387cdd7d3f7ead6799e774dfb366803e7e487.svg

Overwriting grob properties set by engravers#

The \override command has the effect of setting the context-wide default for a grob property. Certain engravers, however, write properties in the grobs they create. For instance, the Note_heads_engraver sets the staff-position on freshly instantiated NoteHead grobs based on the pitch in the note event it reads. This makes \override ineffective. The \overrideProperty command sets a property on a grob after it has been created and initialized by its origin engraver. Internally, \overrideProperty uses \applyOutput. The \overrideProperty command takes the grob property path and a value, like \override but without an equals sign.

\version "2.25.8"

{
  \overrideProperty NoteHead.staff-position 50
  c'1
}
Output../../images/d45594dc3e574dcb2701557e20dda7e0c4341a517c288981a6044ab7c1699750.svg

Writing an engraver#

Basics#

Engravers reside in contexts. They are added to them in output definitions. The pattern is:

\layout {
  \context {
    \ContextName
    \consists Some_engraver
  }
}

Here, Some_engraver should be the name of a predefined engraver. They are listed in the Internals Reference, under Engravers and Performers.

The \remove command is the opposite of \consists and suppresses an engraver from a context where it would have been active by default.

For engravers defined in Scheme and not registered, the argument is no longer a string, but a procedure: #Some_engraver, where Some_engraver takes a context and uses the make-engraver macro to return an engraver [1].

Here is a template for writing an engraver. As you can see, there are many possible sections where you can add code. All of them are optional.

#(define (My_engraver context)
   (let (variables...)
     (make-engraver
      ((initialize engraver)
       ...)
      ((start-translation-timestep engraver)
       ...)
      (listeners
       ((event-class-1 engraver event)
        ...)
       ((event-class-2 engraver event)
        ...)
       ...)
      ((pre-process-music engraver)
       ...)
      ((process-music engraver)
       ...)
      (acknowledgers
       ((grob-interface-1 engraver grob source-engraver)
        ...)
       ((grob-interface-2 engraver grob source-engraver)
        ...)
       ...)
      (end-acknowledgers
       ((grob-interface-1 engraver grob source-engraver)
        ...)
        ((grob-interface-2 engraver grob source-engraver)
         ...)
       ...)
      ((process-acknowledged engraver)
       ...)
      ((stop-translation-timestep engraver)
       ...)
      ((finalize engraver)
       ...))))

\layout {
  \context {
    \SomeContext
    \consists #My_engraver
  }
}

Don’t panic! The rest of this section explains the hooks one by one.

As an overview to whet your appetite, this is the general process followed by an engraver:

initialize

For each point of time:

start-translation-timestep

For each event matching one of the event classes defined in listeners:

call appropriate listeners

pre-process-music

process-music

While there are pending grobs:

For each created grob matching one of the interfaces defined in acknowledgers:

call appropriate acknowledgers

process-acknowledged

stop-translation-timestep

finalize

The variables… are in a Scheme closure and therefore internal to the engraver.

The ellipsis in every method stands for arbitrary Scheme expressions. This is similar to the body of a define or lambda function definition or the body of a let form. The expressions are evaluated in order. Their return values are not important because engravers rely on side-effects.

The time step cycle#

The music is iterated following time. All engravers are synchronized on a cycle called the „time step cycle“. A so-called „time step“ happens for each musical moment in the score. If there are simultaneous voices, time steps are arranged so that every event is played in some time step. Schematically (x represents a note):

4 4                      x---------------- x------------------
\tuplet 3/2 { 4 4 4 }    x---------- x---------- x------------

Time steps               [ time step ][t.s.][t.s.][ time step ]

When a time step starts, the code in start-translation-timestep is called in all engravers. Quite naturally, this is paired with stop-translation-timestep at the end of the time step.

Furthermore, on its very first time step, the initialize method is called. It may be used to set up state.

Note that for this first time step specifically, start-translation-timestep is not called. This is because contexts are created through music (the \new command), and music is iterated in time steps, so the context creation may actually happen after the start of a time step.

The initialize method is paired with finalize, called in the end of the life of an engraver. This method is for bookkeeping, for example, warning about an unterminated spanner. The stop-translation-timestep method is called before finalize, as one would expect.

Processing stream events#

In the listeners body of the engraver are methods specific to certain event classes. When a corresponding stream event is broadcast, these methods are called with the engraver itself and the event as arguments.

(listeners
 ((event-class-1 engraver event)
  ...)
 ((event-class-2 engraver event)
  ...))

Event broadcasting follows the context hierarchy. Events heard in a context are also heard in its parents. This means that an engraver residing in Voice context is appropriate to listen to note events, for example, whereas an engraver in Staff context is suited to listening key changes, which might come indifferently from any of the Voice children of the Staff.

It is important to know that grobs should not be created in listeners. This is due to the unspecified order of events. When iterating, for example, simultaneous music, it is unclear what order the events should arrive in:

\version "2.25.8"

\new Staff <<
  { \time 3/4 c'2. }
  \\
  { \override Staff.TimeSignature.color = red c2. }
>>
Output../../images/0ba33a3def2bd87429a3fd9b950dc2c802f12644ed8bdb4bd7b2d0c854fa25f7.svg

In the above example, the OverrideProperty event corresponding to the \override command may well be broadcast after the TimeSignatureEvent. Yet, we want it to affect the created time signature. If the time signature is created before this event can be heard, the override will be „missed“.

This is why the workflow of engravers is to use listeners to record the events they are interested in. Listeners may also set context properties. Then, when all events have been heard, the process-music method is called. This is where grobs should be created, and no earlier.

When you set a context property, it is often the case that you would like other engravers to be able to read this property in process-music while they create their grobs. While listeners often suffice, sometimes, you would like to set it to a value that depends on several events instead of just one. Also, sometimes the property does not depend on events at all but does depend on properties set by other engravers in start-translation-timestep. For these cases, there is a pre-process-music hook that runs between listeners and process-music. It should normally not be used for creating grobs, only for performing tasks that affect other engravers in process-music, such as setting properties.

Example for setting properties in pre-process-music: Force_chord_at_bar_start_engraver#

In a ChordNames context, when the chordChanges property is active, identical consecutive chords are merged. This engraver implements a behavior that is a mix of chordChanges = ##t and chordChanges = ##f: consecutive chords within one measure are merged, but a chord is always printed at the start of a measure, even if it is the same as the previous chord. Three hooks are used to this end:

  • initialize, to start with chordChanges = ##t,

  • pre-process-music, to temporarily set chordChanges = ##f at the beginning of each bar, which is recognized through the measureStartNow property set by Timing_translator,

  • stop-translation-timestep, to reset chordChanges to #t.

This engraver is so simple that it does not need any variables in a let around make-engraver (this is rarely the case).

Note the use of pre-process-music. start-translation-timestep would be too early because Timing_translator sets measureStartNow in start-translation-timestep, so the result would depend on which of Timing_translator and Force_chord_at_bar_start_engraver runs its start-translation-timestep method first. This type of dependency on engraver order is generally frowned upon. On the other hand, process-music would be too late, since Chord_name_engraver reads chordChanges in process-music. Therefore, pre-process-music is exactly the right time.

Also note that measureStartNow is not set at the very beginning of the piece, but this is not an issue in this case (the first chord is always printed anyway).

\version "2.25.8"

#(define (Force_chord_at_bar_start_engraver context)
   (make-engraver
    ((initialize engraver)
     (ly:context-set-property! context 'chordChanges #t))
    ((pre-process-music engraver)
     (when (ly:context-property context 'measureStartNow #f)
       (ly:context-set-property! context 'chordChanges #f)))
    ((stop-translation-timestep engraver)
     (ly:context-set-property! context 'chordChanges #t))))

ch = \chordmode { c1 g2 g2 g2 c2:7 f2 }

\layout {
  indent = 40
  \context {
    \Score
    \remove System_start_delimiter_engraver
  }
  \context {
    \ChordNames
    \consists Bar_engraver
    \consists Instrument_name_engraver
    \consists Staff_symbol_engraver
    \override StaffSymbol.line-count = 0
    \override BarLine.bar-extent = #'(0 . 2)
  }
}

<<
  \new ChordNames \with {
    instrumentName = "Normal"
  } \ch
  \new ChordNames \with {
    instrumentName = \markup \typewriter chordChanges
    chordChanges = ##t
  } \ch
  \new ChordNames \with {
    instrumentName = \markup { engraver }
    \consists #Force_chord_at_bar_start_engraver
  } \ch
>>
Output../../images/320200ba71785a74ab86c1ff09675f2567c9db85aef57fdb6d6be6d3104abe89.svg

Creating grobs#

ly:engraver-make-grob is the basic interface to create a grob from an engraver.

(ly:engraver-make-grob engraver grob-type cause)

Return a newly created graphical object.

The grob-type may be any name of a grob, given as symbol. The cause is either a stream event, or another grob. When no particular cause can be given for a grob (e.g., a bar line), it should be the empty list.

As explained in Grob flavors, grobs come in several flavors, most importantly and spanners. The grob type normally mandates use as item or spanner. However, it happens that a grob can be used both ways. This is mainly the case for so-called „sticky grobs“, which attach to another arbitrary grob, such as footnotes, balloons and parentheses. While many grobs attach to other grobs (e.g., articulations attach to note heads), sticky grobs are special because the grob they attach to, called their „host“, is arbitrary and can therefore be either an item or a spanner. In turn, this necessitates creating the sticky grob either as item or spanner depending on the flavor of its host. The following function supports this common case:

(ly:engraver-make-sticky engraver grob-type host cause)

Create a sticky grob that with the same flavor as the grob host, and arranges for it to attach to host by setting its parents and bounds.

grob-type must be a sticky grob type. Namely, it must have the sticky-grob-interface.

Example for creating grobs: Tacet_engraver#

This engraver prints a text mark that reads „Tacet“ whenever a sequence of multi-measure rests starts. To this end, it has three listeners, one listener for multi-measure-rest-event to determine when such a sequence starts, and two listeners, for note-event and rest-event, to determine when it ends (we don’t want to create another, redundant „Tacet“ before the sequence of consecutive multi-measure rests has ended). To create the TextMark grob, it uses ly:engraver-make-grob, since TextMark is not a sticky grob, and sets its text property to "Tacet".

\version "2.25.8"

#(define (Tacet_engraver context)
   (let ((in-tacet #f)
         (mmrest-event #f))
     (make-engraver
      (listeners
       ((multi-measure-rest-event engraver event)
        (set! mmrest-event event))
       ((note-event engraver event)
        (set! in-tacet #f))
       ((rest-event engraver event)
        (set! in-tacet #f)))
      ((process-music engraver)
       (when (and mmrest-event (not in-tacet))
         (set! in-tacet #t)
         (let ((grob (ly:engraver-make-grob engraver 'TextMark mmrest-event)))
           (ly:grob-set-property! grob 'text "Tacet"))))
      ((stop-translation-timestep engraver)
       (set! mmrest-event #f)))))

\new Staff \with {
  \consists #Tacet_engraver
} {
  R1
  c'4 8 8 4 4
  R1*2
  e'4 8 8 4 4
  R1 R1
  g'4 8 8 4 4
}
Output../../images/81c86c92f78b5e90c7fd8c7542bfc964050a17e6e8953487c7fe2cd191f7389a.svg

Time management#

You can know where the translation process is in the time line using this function on the context given as argument to the engraver:

(ly:context-current-moment context)

Return the current point of time of the translation process that is happening on this context, as a Moment object.

Note that all contexts are always synchronized, so this function will give the same result on the parent of the context, for example.

Of course, you can also use this function on the context you have in a function passed to \applyContext. It is just typically more useful in an engraver.

Usually, the grace part of the returned moment is zero. If there is a grace note, the grace part of the current moment in the time step where that note is processed will be negative.

Certain events, such as note, rest and multi-measure rest events, have a musical length. This is not reflected in any way in how the engraver receives them: the engraver is only notified of the event when it starts, not when it ends. However, an engraver can read the event’s length property, which is a Moment object.

Although this could theoretically suffice, a little complication arises with grace notes. When the music expression \grace { c8 } is iterated, the resulting note event has a length property equal to the moment with main part 1/8, and grace part zero, since the length of a note is computed independently from whether it is inserted into a grace or not. Therefore, careless use of (ly:event-property <event> 'length) without accounting for grace notes will lead to bugs. To help with writing grace-correct engravers, there is a convenience function, added in LilyPond 2.25.1:

(ly:event-length event [moment])

Return the length of event assuming that it happens at moment. In the usual case where moment has a zero grace part, this is simply (ly:event-property event 'length). However, in case moment’s grace part is nonzero (normally negative), the length is converted to a grace-only moment.

moment can also be left out, in which case this is just a shortcut for (ly:event-property event 'length).

Time steps can also be triggered without events. The main case is with bar lines: with input such as { c'1*2 }, a bar line is added in the middle of the C note, even though there was no actual event at that point. This can happen thanks to Timing_translator, one of the engravers running by default, which adds time steps for all moments where a measure ends. Starting with LilyPond 2.25.1, the same can also be done from custom engravers.

(ly:context-schedule-moment context moment)

Request that a time step be performed at the given moment (which must lie in the future, i.e., be greater than the current moment).

Example for using event lengths: Auto_breathe_engraver#

This engraver listens to rest events and records the moment where each rest event will end using ly:event-length. It always keeps the end moment of the latest rest event heard. If, in process-music, the current moment is the same as this end moment, this means that a rest ended, without a new rest (with a later end moment) having started in this time step. Under this condition, the engraver prints a breathing sign to signify the end of the musical phrase. The breathing sign is initialized using ly:breathing-sign::set-breath-properties, which mimics what Breathing_sign_engraver does.

\version "2.25.8"

#(define (Auto_breathe_engraver context)
   (let ((previous-rest-event #f)
         (previous-rest-end-moment #f))
     (make-engraver
      (listeners
       ((rest-event engraver event)
        (set! previous-rest-event event)
        (let ((current (ly:context-current-moment context)))
          (set! previous-rest-end-moment
                (ly:moment-add current (ly:event-length event current))))))
      ((process-music engraver)
       (when (equal? previous-rest-end-moment (ly:context-current-moment context))
         (let ((grob (ly:engraver-make-grob engraver 'BreathingSign previous-rest-event)))
           (ly:breathing-sign::set-breath-properties grob context 'comma)))))))

\layout {
  \context {
    \Voice
    \consists #Auto_breathe_engraver
    % https://gitlab.com/lilypond/lilypond/-/issues/6273
    \override BreathingSign.extra-spacing-height = #'(-inf.0 . +inf.0)
  }
}

\relative {
  \time 9/8
  \partial 8
  a8 b4 d8 f4. r4 r8
  g,8 a c r4 ees8 g4.
}
Output../../images/3fbbd6fd0229faf89006d5d207482d71b53d7cb1b14347b34259ff1fbaf56147.svg

Acknowledging grobs#

With listeners and the process-music hook, many cases for grob creation are covered. However, grobs also require links between different types. Dots objects are associated to NoteHead, for instance. For the sake of modularity, they are created by separate engravers. This is why a mechanism exists for engravers to process grobs created in other engravers. This is called acknowledgers.

Every engraver can exclusively acknowledge grobs created by engravers whose enclosing context is a direct or indirect child of the engraver’s context. An engraver in Voice context acknowledges all grobs created from engravers in this Voice; an engraver in Staff acknowledges all those created from engravers in this Staff and engravers in children Voices; etc.

The body of acknowledgers in make-engraver resembles that of listeners.

(acknowledgers
 ((grob-interface-1 engraver grob source-engraver)
  ...)
 ((grob-interface-2 engraver grob source-engraver)
  ...)
 ...)

Every acknowledger is called with three arguments: the engraver it is operating in, the grob, and the engraver where the grob has been created. The function ly:translator-context can provide the context in which the source engraver lives.

Just like with listeners, acknowledgers should generally be used to record the grobs, not process them directly to create other grobs, since other engravers may change properties of the acknowledged grobs in their own acknowledgers. The equivalent of process-music for acknowledgers is process-acknowledged.

((process-acknowledged engraver)
 ...)

New grobs may be created in process-acknowledged. This leads to a new cycle of acknowledgers, then process-acknowledged.

Engravers do not acknowledge their own grobs.

Example for acknowledging grobs: Balloon_notes_engraver#

This engraver adds a balloon on every note, indicating its pitch. Since balloons are sticky grobs, this is done using ly:engraver-make-sticky. The engraver sets a bunch of properties on the balloon. In particular, X-offset and Y-offset, which are normally taken from an AnnotateOutputEvent (from the call to \balloonText), are set to values making the slopes increase vertically in a chord. The annotation-balloon property is deactivated to suppress the rectangle around every note head. The pitches are converted to strings through the note-name->string function, using the english input language.

Note the frequent pattern of resetting the list of acknowledged grobs at the end of process-acknowledged, to avoid processing grobs twice if there are further acknowledge cycles.

\version "2.25.8"

#(define (Balloon_notes_engraver context)
   (let ((note-heads '()))
     (make-engraver
      (acknowledgers
       ((note-head-interface engraver grob source-engraver)
        (set! note-heads (cons grob note-heads))))
      ((process-acknowledged engraver)
       (for-each
        (lambda (i note-head)
          (let* ((note-event (event-cause note-head))
                 (pitch (ly:event-property note-event 'pitch))
                 (pitch-string
                   (string-capitalize
                     (note-name->string pitch 'english)))
                 (balloon (ly:engraver-make-sticky engraver
                                                   'BalloonText
                                                   note-head
                                                   note-head)))
            (ly:grob-set-property! balloon 'font-size -3)
            (ly:grob-set-property! balloon 'font-series 'bold)
            (ly:grob-set-property! balloon 'X-offset -2)
            (ly:grob-set-property! balloon 'Y-offset (+ i 0.2))
            (ly:grob-set-property! balloon 'annotation-balloon #f)
            (ly:grob-set-property! balloon 'text pitch-string)
            (ly:grob-set-property! note-head
                                   'extra-spacing-width
                                   '(-3.5 . 0))))
        (reverse! (iota (length note-heads)))
        note-heads)
      (set! note-heads '())))))

\layout {
  \context {
    \Voice
    \consists #Balloon_notes_engraver
  }
}

{
  <e' g' b'>1
  <e' g' a'>1
}
Output../../images/ac467fdd4134a26b0aaa76c19cba83f2c1f76b2b750a7e725e32463819a0de7a.svg

End acknowledgers#

Spanners are not finished in a single time step. Their bounds must be set in two different time steps, and they may be terminated in reaction to an event, like hairpins with \!.

In addition to acknowledgers, which is triggered at grob creation time, the end-acknowledgers body contains acknowledgers triggered at the time a spanner ends. This time is announced by the engraver responsible for ending it. Custom engravers should also announce spanner ends.

(ly:engraver-announce-end-grob engraver spanner cause)

Announce the end of spanner for other engravers.

Like the one for ly:engraver-make-grob, the cause argument should be an event, another grob, or the empty list.

Example for end acknowledgers: No_break_during_tie_engraver#

This engraver prevents line breaks from crossing ties. This is achieved through setting the forbidBreak property of the Score context. Note the logic with the tie-in-progress variable. The break should be forbidden on the left of the note head even when the tie ends on this head, and we do not want to disallow breaks on the left of a head that starts a tie. This is why, as is commonly done, the acknowledgers only record the ties. The final processing is done in stop-translation-timestep (often this is rather in process-acknowledged).

\version "2.25.8"

#(define (No_break_during_tie_engraver context)
   (let ((tie-in-progress #f)
         (acknowledged-start-tie #f)
         (acknowledged-end-tie #f))
     (make-engraver
      ((pre-process-music engraver)
       (when tie-in-progress
         (let ((score (ly:context-find context 'Score)))
           (ly:context-set-property! score 'forbidBreak #t))))
      (acknowledgers
       ((tie-interface engaver grob source-engraver)
        (set! acknowledged-start-tie #t)))
      (end-acknowledgers
       ((tie-interface engraver grob source-engraver)
        (set! acknowledged-end-tie #t)))
      ((stop-translation-timestep engraver)
       (when acknowledged-end-tie
         (set! tie-in-progress #f)
         (set! acknowledged-end-tie #f))
       (when acknowledged-start-tie
         (set! tie-in-progress #t)
         (set! acknowledged-start-tie #f))))))

music = {
  \repeat unfold 20 c'1~ c'1
  c'1
  \repeat unfold 20 c'1~ c'1
}

\new Voice \music
\new Voice \with { \consists #No_break_during_tie_engraver } \music
Output../../images/ee770e978e1de0520ec6a9e587f56d21375b11d37e6b5c5ea352c641d43c8ee9.svg

Setting grob parents and spanner bounds#

One of the responsibilities of engravers when creating grobs is ensuring that they have a parent on both axes, and that spanners have bounds.

At every point in time, a context has two important properties: currentMusicalColumn and currentCommandColumn. They are the default X parents for all items created in the time step. The musical column is used for all musical items and vice versa. A non-musical item is defined as an item having the non-musical property set to true, or a child of such an item. All other items are considered musical.

For spanners bounds, there is no default and the bounds must be set explicitly. For spanners that have no particular items as bounds, either the musical or the non-musical columns should be used. The X parent of a spanner defaults to its left bound.

On the Y axis, items and spanners behave in the same way. The Axis_group_engraver creates VerticalAxisGroup grobs, which provide a vertical baseline for grobs created in the same Staff-like context (Staff, Lyrics, Dynamics, etc.). It acknowledges all grobs created in its context, and sets their parent to this VerticalAxisGroup if not already set. Grobs created in higher contexts such as Score and StaffGroup default to having the global System grob as their Y parent.

Example for setting parents: Auto_stanza_engraver#

Usually, you need to manually add \set stanza = "x." commands in each verse of lyrics. This engraver automates it in the common case. It acknowledges VerticalAxisGroups (through hara-kiri-group-spanner-interface), and for each axis group that comes from a Lyrics context, creates a StanzaNumber with that axis group as Y parent. (Note that an alternative would be to create those StanzaNumber grobs on staff level, which would make their Y parent set automatically.) It also acknowledges the VerticalAlignment grob that these vertical axis groups all belong to. At the end of the first time step, it reads the elements array from that grob, which contains the axis groups in vertical order, and it sets the text of each created stanza number accordingly.

\version "2.25.8"

#(use-modules ((ice-9 hash-table) #:select (alist->hashq-table)))

#(define (Auto_stanza_engraver context)
   (let ((axis-groups '())
         (stanza-numbers '())
         (vertical-alignment #f))
     (make-engraver
      (acknowledgers
       ((hara-kiri-group-spanner-interface engraver grob source-engraver)
        (let ((source-context (ly:translator-context source-engraver)))
          (when (ly:context-find source-context 'Lyrics)
            (set! axis-groups (cons grob axis-groups)))))
       ((align-interface engraver grob source-engraver)
        (set! vertical-alignment grob)))
      ((process-acknowledged engraver)
       (for-each
        (lambda (axis-group)
          (let ((stanza-number
                 (ly:engraver-make-grob engraver 'StanzaNumber axis-group)))
            (ly:grob-set-parent! stanza-number Y axis-group)
            (set! stanza-numbers (cons stanza-number stanza-numbers))))
        axis-groups)
       (set! axis-groups '()))
      ((stop-translation-timestep engraver)
       (when vertical-alignment
         (let ((group-to-stanza (alist->hashq-table
                                 (map (lambda (stanza-number)
                                        (cons (ly:grob-parent stanza-number Y)
                                              stanza-number))
                                      stanza-numbers)))
               (i 1))
           (for-each
            (lambda (group)
              (let ((stanza (hashq-ref group-to-stanza group)))
                (when stanza
                  (let ((i-str (number->string i)))
                    (ly:grob-set-property! stanza 'text (string-append i-str ".")))
                  (set! i (1+ i)))))
            (ly:grob-array->list (ly:grob-object vertical-alignment 'elements #f))))
         (set! vertical-alignment #f))))))

\layout {
  \context {
    \Score
    \consists #Auto_stanza_engraver
  }
}

<<
  \new Voice = melody \fixed c' { c4 c g g a a g2 }
  \new Lyrics \lyricsto melody { Twin -- kle, twin -- kle, lit -- tle star… }
  \new Lyrics \lyricsto melody { When the bla -- zing sun is gone… }
  \new Lyrics \lyricsto melody { Then the tra -- veller in the dark… }
>>
Output../../images/c222521dda62fb3a9b0a0688460013a3136b7b1186e781561a436b82fde154d1.svg

Example for setting bounds: Align_all_dynamics_engraver#

This engraver aligns all dynamics on the same vertical position. This is more or less equivalent to using a separate Dynamics context, except that the dynamics can be entered in the main music input without resorting to spacer rests.

This is achieved by creating a single DynamicLineSpanner for the entire score, unlike the default Dynamic_align_engraver, which makes one for every sequence of consecutive dynamics.

The dynamics are added to the spanner using ly:axis-group-interface::add-element, which sets pointers in the object to its axis group in addition to making the group parent of the object.

The bounds of the spanner are non-musical columns.

\version "2.25.8"

#(define (Align_all_dynamics_engraver context)
   (let ((line-spanner #f))
     (make-engraver
      ((process-music engraver)
       (when (not line-spanner)
         (set! line-spanner
               (ly:engraver-make-grob engraver 'DynamicLineSpanner '()))
         (let ((column (ly:context-property context 'currentCommandColumn)))
           (ly:spanner-set-bound! line-spanner LEFT column))))
      (acknowledgers
       ((dynamic-interface engraver grob source-engraver)
        (ly:axis-group-interface::add-element line-spanner grob)))
      ((finalize engraver)
       (let ((column (ly:context-property context 'currentCommandColumn)))
         (ly:spanner-set-bound! line-spanner RIGHT column))))))

\layout {
  \context {
    \Voice
    \remove Dynamic_align_engraver
    \consists #Align_all_dynamics_engraver
  }
}

\new Staff \relative {
  \override DynamicLineSpanner.direction = #UP
  c'2\< d4 e |
  c4 e e,2\f |
  g'4\dim a g a |
  c1\p |
}
Output../../images/93947b5127aaf4fd15dab7a60951b14cc29ab4a15c91cab43acdc0fea8e2ee80.svg

Killing grobs#

Time is sequential, with no look-ahead possibilities. If it is later realized that a grob is not needed, the grob should be killed using ly:grob-suicide!.

Example for killing grobs: Voice_line_engraver#

This engraver adds lines between note heads in a melody. Observe the use of ly:grob-suicide!: the voice follower must be started whenever a note head is found, without knowing if the next time step is going to contain a note or a rest. Afterwards, if there is no note head in the time step, the previously created voice follower is killed.

In addition, voice followers are not displayed when there is a slur. Note that slurs are not announced in the time step where they end but in the following time step. Therefore, some trickery is required to suicide the right grobs and keep state properly. To make that logic more readable, a separate engraver is used. When you have a complex engraver, it can become hard to keep track of the different states of the engraver. In those cases, it is sometimes useful to split the engraver into several engravers, each of which has simpler invariants.

This example has pretty unclear musical interest. There is some fun to it, however.

\version "2.25.8"

#(define (Voice_line_engraver context)
   (let (
         ;; Current follower
         (follower #f)
         ;; Note head grob acknowledged
         (note-head #f)
         ;; Moment at which the follower should end. If there is no note head
         ;; at that moment (e.g., because there is a rest), it is removed.
         (expected-end-mom #f))
     (make-engraver
      (acknowledgers
       ((note-head-interface engraver grob source-engraver)
        (set! note-head grob)))
      ((process-acknowledged engraver)
       (when note-head
         ;; End the previous follower on this note head.
         (when follower
           (ly:spanner-set-bound! follower RIGHT note-head)
           (ly:engraver-announce-end-grob engraver follower note-head)
           (set! follower #f)
           (set! expected-end-mom #f))
         ;; Create a new follower starting from this note head.
         (set! follower (ly:engraver-make-grob engraver 'VoiceFollower note-head))
         (ly:spanner-set-bound! follower LEFT note-head)
         ;; Record the moment at which we expect the follower to end.
         (set! expected-end-mom
               (let ((current (ly:context-current-moment context))
                     (note-event (ly:grob-property note-head 'cause)))
               (ly:moment-add current (ly:event-length note-event current))))
         (set! note-head #f)))
      ((stop-translation-timestep engraver)
       ;; If the follower reached its expected end moment without finding
       ;; a note head to end on (e.g., because of a rest), remove it.
       (let ((current (ly:context-current-moment context)))
         (when (and expected-end-mom (moment<=? expected-end-mom current))
           (ly:grob-suicide! follower)
           (set! follower #f)
           (set! expected-end-mom #f)))
       ;; Bookkeeping
       (set! note-head #f))
      ((finalize engraver)
       ;; Remove any unterminated follower
       (when follower
         (ly:grob-suicide! follower))))))

#(define (Remove_voice_line_when_slur_engraver context)
   (let (
         ;; Any voice follower started in this time step
         (started-voice-follower #f)
         ;; Any voice follower ended in this time step
         (ended-voice-follower #f)
         ;; The currently "active" voice follower; a follower is active
         ;; from its start time step included to its end time step excluded.
         (active-voice-follower #f)
         ;; The voice follower that was active at the previous time step.
         (previous-active-voice-follower #f)
         ;; Any slur started in this time step
         (started-slur #f)
         ;; Any slur started in the previous time step
         (previous-started-slur #f)
         ;; Any slur of which we acknowledge the end, meaning that it ended
         ;; in the *previous* time step.
         (previous-ended-slur #f)
         ;; The slur that was active in the previous time step.
         (previous-active-slur #f))
     (make-engraver
      (acknowledgers
       ((line-spanner-interface engraver grob source-engraver)
        ;; Ideally, we'd have a specific interface for VoiceFollower,
        ;; but it doesn't exist.
        (when (eq? 'VoiceFollower (grob::name grob))
          (set! started-voice-follower grob)))
       ((slur-interface engraver grob source-engraver)
        (set! started-slur grob)))
      (end-acknowledgers
       ((line-spanner-interface engraver grob source-engraver)
        (when (eq? 'VoiceFollower (grob::name grob))
          (set! ended-voice-follower grob)))
       ((slur-interface engraver grob source-engraver)
        (set! previous-ended-slur grob)))
      ((stop-translation-timestep engraver)
       ;; Determine if there was an active slur in the previous time step.
       (when previous-ended-slur
         (set! previous-active-slur #f)
         (set! previous-ended-slur #f))
       (when previous-started-slur
         (set! previous-active-slur previous-started-slur))
       ;; If a voice follower and a slur were both active in the previous
       ;; time step, remove the voice follower.
       (when (and previous-active-voice-follower previous-active-slur)
         (ly:grob-suicide! previous-active-voice-follower))
       ;; Determine if there was an active voice follower in this time step
       (when ended-voice-follower
         (set! active-voice-follower #f)
         (set! ended-voice-follower #f))
       (when started-voice-follower
         (set! active-voice-follower started-voice-follower)
         (set! started-voice-follower #f))
       ;; Set previous-* variables for the next time step.
       (set! previous-active-voice-follower active-voice-follower)
       (set! previous-started-slur started-slur)
       (set! started-slur #f)))))


\layout {
  \context {
    \Voice
    \consists #Voice_line_engraver
    \consists #Remove_voice_line_when_slur_engraver
    \override VoiceFollower.style = #'dashed-line
    \slurDashed
  }
}

\relative {
  \override Score.SpacingSpanner.spacing-increment = 4
  d'16( e f8) e d a' d4 a8 |
  bes8 g16( e) a8 f16( d) g8 e16( cis) a8 bes'8~ |
  bes8 g16( e) a,8 cis'8~ cis bes16( g) a,8 e''~ |
  e8 cis16( a) bes( g a f) g( e f d) e( cis d b) |
  cis( a b cis) d( e f g) a( bes c8) c16( d ees8) |
  fis,8 g cis, d gis, r a r |
}
Output../../images/0c67ec9b509c4730a0840cb00c3729da8087f7501c41905219442374fbc8e39c.svg