hly-0.1: Haskell LilyPond

Music.LilyPond.Light

Contents

Synopsis

Music category predicates

is_grace_skip :: Music -> BoolSource

These are required to avoid issues in lilypond (see manual)

Pitch

r_acc :: Music -> MusicSource

Add reminder accidental to note.

c_acc :: Music -> MusicSource

Add cautionary accidental to note.

clr_acc :: Music -> MusicSource

Remove any reminder or cautionary accidentals at note or chord.

Rests

r :: Duration -> MusicSource

Construct rests.

empty_measure :: Integer -> Integer -> MusicSource

Create an empty measure for the specified time signature.

null_measure :: Integer -> Integer -> MusicSource

Like empty_measure, but with an invisible rest.

measure_rest :: Integer -> Integer -> MusicSource

Like empty_measure but write time signature.

measure_null :: Integer -> Integer -> MusicSource

Like measure_rest but write time signature.

Measures

data Measure Source

Constructors

Measure [M_Annotation] [Music] 

Tuplets

edit_dur :: (Duration -> Duration) -> Music -> MusicSource

Apply fn to the duration of x, if it has a duration.

tuplet :: Tuplet_T -> [Music] -> MusicSource

Temporal scaling of music (tuplets).

tuplet_below :: Tuplet_T -> [Music] -> MusicSource

Tuplet variants that set location, and then restore to neutral.

scale_durations :: Tuplet_T -> [Music] -> MusicSource

Like tuplet but does not annotate music, see also ts_set_fraction.

Time signatures

time_signature :: TimeSignature -> MusicSource

Construct time signature.

with_time_signature :: TimeSignature -> [Music] -> MusicSource

Allow proper auto-indenting of multiple measures with the same time signature.

ts_whole_note :: TimeSignature -> [Duration]Source

Tied, non-multiplied durations to fill a whole measure.

ts_use_fractions :: MusicSource

Command to request that 44 and 22 etc. are typeset as fractions.

ts_set_fraction :: Integer -> Integer -> MusicSource

Set the printed time-signature fraction.

Key signatures

key :: Music -> Mode_T -> MusicSource

Construct key signature.

Repetition

std_repeat :: Integer -> [Music] -> MusicSource

Construct standard (two times) repeat.

Annotations

allows_annotations :: Music -> BoolSource

Can a music element be annotated?

add_annotation :: Annotation -> Music -> Maybe MusicSource

Add an annotation to music element.

add_annotation_err :: Annotation -> Music -> MusicSource

Add an annotation to music element or error.

(&) :: Music -> Annotation -> MusicSource

Add an annotation to music element, or error.

(&#) :: Pitch -> Annotation -> MusicSource

Add an annotation to a pitch.

perhaps_annotate :: Annotation -> Music -> MusicSource

Add an annotation to music element.

beam :: [Music] -> MusicSource

Manual beaming.

note_annotate :: Annotation -> Music -> MusicSource

Add an annotation to a note element, else identity.

initial_note_chord_annotate :: Annotation -> [Music] -> [Music]Source

Annotate the first note/chord element.

Indirect annotations

Octave

note_edit_octave :: (Integer -> Integer) -> Music -> MusicSource

Shift the octave of a note element, else identity.

note_shift_octave :: Integer -> Music -> MusicSource

Shift the octave of a note element, else identity.

Beaming

p_and :: (t -> Bool) -> (t -> Bool) -> t -> BoolSource

Predicate combinators.

p_or :: (t -> Bool) -> (t -> Bool) -> t -> BoolSource

span_r :: (a -> Bool) -> [a] -> ([a], [a], [a])Source

perhaps_beam :: [Music] -> [Music]Source

Beam if at least two elements.

beam_notes :: [Music] -> MusicSource

Beam interior notes/chords (ie. skip exterior non-note/non-chords).

Duration

(##) :: Pitch -> Duration -> MusicSource

Add duration to pitch to make a note.

(#) :: Music -> Duration -> MusicSource

Add duration to pitch to make a note.

Chords

chd_p :: [Pitch] -> Duration -> MusicSource

Construct chord.

Commands

bar_number_check :: Integer -> MusicSource

Construct bar number check.

change :: String -> MusicSource

Change staff.

partial :: Duration -> MusicSource

Indicate initial partial measure.

Staff and Parts

staff :: Staff_Name -> [Music] -> StaffSource

Construct staff.

rhythmic_staff :: Staff_Name -> [Music] -> StaffSource

Construct rhythmic staff.

text_staff :: Staff_Name -> String -> [Music] -> StaffSource

Construct staff with text underlay.

piano_staff :: Staff_Name -> [[Music]] -> StaffSource

Construct piano staff. For two staff piano music the staffs have identifiers rh and lh.

grand_staff' :: Staff_Name -> [Staff_Name] -> [[Music]] -> StaffSource

Variant with names for each staff.

Aliases

polyphony :: Music -> Music -> MusicSource

Interior polyphony. For two part music on one staff see two_part_staff.

Noteheads

cross_noteheads :: MusicSource

Request cross note-heads.

revert_noteheads :: MusicSource

Revert to standard note-heads.

Rests

join_rests :: [Music] -> [Music]Source

Joins directly adjacent rest elements.