hly-0.14: Haskell LilyPond

Safe HaskellSafe-Inferred

Music.LilyPond.Light.Notation

Contents

Synopsis

Music category predicates

is_grace_skip :: Music -> BoolSource

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

Pitch

clr_acc :: Music -> MusicSource

Remove any reminder or cautionary accidentals at note or chord.

Rests

rest :: Duration -> MusicSource

Construct rests.

mm_rest :: Time_Signature -> MusicSource

Multi-measure variant of r.

skip :: Duration -> MusicSource

Non-printing variant of rest.

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.

Tuplets

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

Apply a Duration function to a Music node, if it has a duration.

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

Temporal scaling of music (tuplets).

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

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

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 :: Time_Signature -> MusicSource

Construct time signature.

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

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

ts_use_fractions :: MusicSource

Command to request that 4/4 and 2/2 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.

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.

Duration

(##@) :: Pitch -> Duration_A -> MusicSource

Add Duration_A to Pitch to make a Note Music element.

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

Add Duration to Pitch to make a Note Music element.

(#@) :: Music -> Duration_A -> MusicSource

Add Duration_A to either a Note or Chord Music element.

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

Add Duration to either a Note or Chord Music element.

Chords

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

Construct chord.

Commands

bar_number_check :: Integer -> MusicSource

Construct bar number check command.

bar_numbering :: Bool -> MusicSource

Switch bar numbering visibility.

change :: String -> MusicSource

Change staff.

partial :: Duration -> MusicSource

Indicate initial partial measure.

hairpin_circled_tip :: Bool -> MusicSource

Set or unset the circled-tip hairpin attribute.

hairpin_to_barline :: Bool -> MusicSource

Set or unset the to-barline hairpin attribute.

hairpin_minimum_length :: Maybe Int -> MusicSource

Set or unset the minimum-length hairpin attribute.

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.

polyphony :: Music -> Music -> MusicSource

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

Rests

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

Joins directly adjacent rest elements.

Duration_A functions

type DA_F x = (Duration_A, x) -> MusicSource

Transform ascribed Duration_A value to Music.

da_to_music :: DA_F t -> [(Duration_A, t)] -> [Music]Source

Given DA_F transform, transform set of ascribed Duration_A values to Music.

 import Music.Theory.Duration.Sequence.Notate
 import Music.Theory.Duration.RQ.Tied
 import Music.Theory.Pitch.Name
 import Music.LilyPond.Light.Output.LilyPond
 let {Just d = m_notate True [[(2/3,_f),(1/3,_t)],[(1,_t)],[(1,_f)]]
     ;jn (i,j) = j ##@ i
     ;n = ascribe d [c4,d4]
     ;r = "\\times 2/3 { c' 4 d' 8 ~ } d' 4 ~ d' 4"}
 in ly_music_elem (Join (da_to_music jn n)) == r

da_to_measures :: DA_F x -> Maybe [Time_Signature] -> [[(Duration_A, x)]] -> [Measure]Source

Variant of da_to_music that operates on sets of measures.

Fragment

mk_fragment :: (Double, Double) -> [Music] -> FragmentSource

Make a fragment from a list of Music elements. Width and height are in millimeters.

Stem

Text

Measure operations

mm_delete_redundant_ts :: [Measure] -> [Measure]Source

Delete redundant (repeated) time signatures.

 let mm = [Measure [Time (3,4)] [],Measure [Time (3,4)] []]
 in mm_delete_redundant_ts mm == [Measure [Time (3,4)] [],Measure [] []]