Safe Haskell | Safe-Inferred |
---|
- is_music_c :: Music_C -> Music -> Bool
- is_note :: Music -> Bool
- is_chord :: Music -> Bool
- is_rest :: Music -> Bool
- is_skip :: Music -> Bool
- is_mm_rest :: Music -> Bool
- is_grace :: Music -> Bool
- is_after_grace :: Music -> Bool
- is_grace_skip :: Music -> Bool
- is_clef :: Music -> Bool
- is_time :: Music -> Bool
- is_tempo :: Music -> Bool
- is_command :: Music -> Bool
- is_barlinecheck :: Music -> Bool
- is_tied :: Music -> Bool
- is_tuplet :: Music -> Bool
- clr_acc :: Music -> Music
- octpc_to_note :: (Octave, PitchClass) -> Music
- rest :: Duration -> Music
- mm_rest :: Time_Signature -> Music
- skip :: Duration -> Music
- empty_measure :: Integer -> Integer -> Music
- null_measure :: Integer -> Integer -> Music
- measure_rest :: Integer -> Integer -> Music
- measure_null :: Integer -> Integer -> Music
- edit_dur :: (Duration -> Duration) -> Music -> Music
- tuplet :: Tuplet_T -> [Music] -> Music
- tuplet_above :: Tuplet_T -> [Music] -> Music
- tuplet_below :: Tuplet_T -> [Music] -> Music
- scale_durations :: Tuplet_T -> [Music] -> Music
- time_signature :: Time_Signature -> Music
- with_time_signature :: Time_Signature -> [Music] -> Music
- ts_use_fractions :: Music
- ts_set_fraction :: Integer -> Integer -> Music
- numeric_time_signature :: Music
- ts_parentheses :: Music
- ts_stencil :: Bool -> Music
- ts_transparent :: Bool -> Music
- ts_all_invisible :: Music
- key :: Music -> Mode_T -> Music
- std_repeat :: Integer -> [Music] -> Music
- note_edit_octave :: (Integer -> Integer) -> Music -> Music
- note_shift_octave :: Integer -> Music -> Music
- tie_r_ann :: [D_Annotation] -> [Annotation]
- da_rest :: Duration_A -> Music
- (##@) :: Pitch -> Duration_A -> Music
- (##) :: Pitch -> Duration -> Music
- (#@) :: Music -> Duration_A -> Music
- (#) :: Music -> Duration -> Music
- chd_p :: [Pitch] -> Duration -> Music
- chd :: [Music] -> Duration -> Music
- bar_number_check :: Integer -> Music
- bar_numbering :: Bool -> Music
- change :: String -> Music
- partial :: Duration -> Music
- hairpin_circled_tip :: Bool -> Music
- hairpin_to_barline :: Bool -> Music
- hairpin_minimum_length :: Maybe Int -> Music
- set_8va_notation :: Music
- name_to_id :: Staff_Name -> Staff_ID
- staff :: Staff_Name -> [Music] -> Staff
- rhythmic_staff :: Staff_Name -> [Music] -> Staff
- text_staff :: Staff_Name -> String -> [Music] -> Staff
- piano_staff :: Staff_Name -> [[Music]] -> Staff
- grand_staff :: Staff_Name -> [[Music]] -> Staff
- staff_group :: Staff_Name -> [[Music]] -> Staff
- rhythmic_grand_staff :: Staff_Name -> [[Music]] -> Staff
- grand_staff' :: Staff_Name -> [Staff_Name] -> [[Music]] -> Staff
- staff_group' :: Staff_Name -> [Staff_Name] -> [[Music]] -> Staff
- two_part_staff :: Staff_Name -> ([Music], [Music]) -> Staff
- instr_name :: Staff_Name -> Staff -> Staff
- resize_staff :: Int -> Staff -> Staff
- score :: [Staff] -> Score
- polyphony :: Music -> Music -> Music
- polyphony' :: [Music] -> [Music] -> Music
- join_rests :: [Music] -> [Music]
- type DA_F x = (Duration_A, x) -> Music
- da_to_music :: DA_F t -> [(Duration_A, t)] -> [Music]
- da_to_measures :: DA_F x -> Maybe [Time_Signature] -> [[(Duration_A, x)]] -> [Measure]
- mk_fragment :: (Double, Double) -> [Music] -> Fragment
- mk_fragment_mm :: (Double, Double) -> [Measure] -> Fragment
- stem_transparent :: Bool -> Music
- text_length_on :: Music
- text_outside_staff_priority :: Maybe Double -> Music
- text_extra_spacing_width :: (Double, Double) -> Music
- mm_delete_redundant_ts :: [Measure] -> [Measure]
Music category predicates
is_music_c :: Music_C -> Music -> BoolSource
is_mm_rest :: Music -> BoolSource
is_after_grace :: Music -> BoolSource
is_grace_skip :: Music -> BoolSource
These are required to avoid issues in lilypond (see manual)
is_command :: Music -> BoolSource
is_barlinecheck :: Music -> BoolSource
Pitch
octpc_to_note :: (Octave, PitchClass) -> MusicSource
Rests
mm_rest :: Time_Signature -> MusicSource
Multi-measure variant of r
.
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
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.
ts_stencil :: Bool -> MusicSource
ts_transparent :: Bool -> MusicSource
Key signatures
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
tie_r_ann :: [D_Annotation] -> [Annotation]Source
da_rest :: Duration_A -> MusicSource
Rest of Duration_A
.
(##@) :: Pitch -> Duration_A -> MusicSource
Add Duration_A
to Pitch
to make a Note
Music
element.
(#@) :: Music -> Duration_A -> MusicSource
Add Duration_A
to either a Note
or Chord
Music
element.
Chords
Commands
bar_number_check :: Integer -> MusicSource
Construct bar number check command.
bar_numbering :: Bool -> MusicSource
Switch bar numbering visibility.
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 -> [[Music]] -> StaffSource
staff_group :: Staff_Name -> [[Music]] -> StaffSource
rhythmic_grand_staff :: Staff_Name -> [[Music]] -> StaffSource
grand_staff' :: Staff_Name -> [Staff_Name] -> [[Music]] -> StaffSource
Variant with names for each staff.
staff_group' :: Staff_Name -> [Staff_Name] -> [[Music]] -> StaffSource
two_part_staff :: Staff_Name -> ([Music], [Music]) -> StaffSource
instr_name :: Staff_Name -> Staff -> StaffSource
resize_staff :: Int -> Staff -> StaffSource
polyphony :: Music -> Music -> MusicSource
Interior polyphony. For two part music on one staff see
two_part_staff
.
polyphony' :: [Music] -> [Music] -> MusicSource
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.
mk_fragment_mm :: (Double, Double) -> [Measure] -> FragmentSource
Measure
variant of mk_fragment
.
Stem
stem_transparent :: Bool -> MusicSource
Text
text_extra_spacing_width :: (Double, Double) -> MusicSource
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 [] []]