hmt-0.15: Haskell Music Theory

Safe HaskellSafe-Inferred
LanguageHaskell98

Music.Theory.Duration

Description

Common music notation duration model.

Synopsis

Documentation

data Duration Source

Common music notation durational model

Constructors

Duration 

Fields

division :: Integer

division of whole note

dots :: Integer

number of dots

multiplier :: Rational

tuplet modifier

duration_meq :: Duration -> Duration -> Bool Source

Are multipliers equal?

duration_compare_meq :: Duration -> Duration -> Maybe Ordering Source

Compare durations with equal multipliers.

order_pair :: Ordering -> (t, t) -> (t, t) Source

sort_pair :: (t -> t -> Ordering) -> (t, t) -> (t, t) Source

Sort a pair of equal type values using given comparison function.

sort_pair compare ('b','a') == ('a','b')

sort_pair_m :: (t -> t -> Maybe Ordering) -> (t, t) -> Maybe (t, t) Source

no_dots :: (Duration, Duration) -> Bool Source

True if neither duration is dotted.

sum_dur_undotted :: (Integer, Integer) -> Maybe Duration Source

Sum undotted divisions, input is required to be sorted.

sum_dur_dotted :: (Integer, Integer, Integer, Integer) -> Maybe Duration Source

Sum dotted divisions, input is required to be sorted.

sum_dur_dotted (4,1,4,1) == Just (Duration 2 1 1)
sum_dur_dotted (4,0,2,1) == Just (Duration 1 0 1)
sum_dur_dotted (8,1,4,0) == Just (Duration 4 2 1)
sum_dur_dotted (16,0,4,2) == Just (Duration 2 0 1)

sum_dur :: Duration -> Duration -> Maybe Duration Source

Sum durations. Not all durations can be summed, and the present algorithm is not exhaustive.

import Music.Theory.Duration.Name
sum_dur quarter_note eighth_note == Just dotted_quarter_note
sum_dur dotted_quarter_note eighth_note == Just half_note
sum_dur quarter_note dotted_eighth_note == Just double_dotted_quarter_note

sum_dur' :: Duration -> Duration -> Duration Source

Erroring variant of sum_dur.

whole_note_division_to_musicxml_type :: Integer -> String Source

Give MusicXML type for division.

map whole_note_division_to_musicxml_type [2,4] == ["half","quarter"]

duration_to_musicxml_type :: Duration -> String Source

Variant of whole_note_division_to_musicxml_type extracting division from Duration.

duration_to_musicxml_type quarter_note == "quarter"

duration_to_lilypond_type :: Duration -> String Source

Give Lilypond notation for Duration. Note that the duration multiplier is not written.

import Music.Theory.Duration.Name
map duration_to_lilypond_type [half_note,dotted_quarter_note] == ["2","4."]

whole_note_division_to_beam_count :: Integer -> Maybe Integer Source

Calculate number of beams at notated division.

whole_note_division_to_beam_count 32 == Just 3

duration_beam_count :: Duration -> Integer Source

Calculate number of beams at Duration.

map duration_beam_count [half_note,sixteenth_note] == [0,2]

duration_recip_pp :: Duration -> String Source

Duration to **recip notation.

http://humdrum.org/Humdrum/representations/recip.rep.html

let d = map (\z -> Duration z 0 1) [0,1,2,4,8,16,32]
in map duration_recip_pp d == ["0","1","2","4","8","16","32"]
let d = [Duration 1 1 (1/3),Duration 4 1 1,Duration 4 1 (2/3)]
in map duration_recip_pp d == ["3.","4.","6."]