| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Music.Theory.Duration.Rq
Contents
Description
Rational quarter-note notation for durations.
Synopsis
- type Rq = Rational
- rq_tuplet_duration_table :: [(Rq, Duration)]
- rq_tuplet_to_duration :: Rq -> Maybe Duration
- rq_plain_duration_tbl :: Dots -> [(Rq, Duration)]
- rq_plain_to_duration :: Dots -> Rq -> Maybe Duration
- rq_plain_to_duration_err :: Dots -> Rq -> Duration
- rq_to_duration :: Dots -> Rq -> Maybe Duration
- rq_to_duration_err :: Show a => a -> Dots -> Rq -> Duration
- rq_is_cmn :: Dots -> Rq -> Bool
- whole_note_division_to_rq :: Division -> Rq
- rq_apply_dots :: Rq -> Dots -> Rq
- duration_to_rq :: Duration -> Rq
- duration_compare_rq :: Duration -> Duration -> Ordering
- rq_mod :: Rq -> Rq -> Rq
- rq_divisible_by :: Rq -> Rq -> Bool
- rq_is_integral :: Rq -> Bool
- rq_integral :: Rq -> Maybe Integer
- rq_derive_tuplet_plain :: [Rq] -> Maybe (Integer, Integer)
- rq_derive_tuplet :: [Rq] -> Maybe (Integer, Integer)
- rq_un_tuplet :: (Integer, Integer) -> Rq -> Rq
- rq_to_cmn :: Rq -> Maybe (Rq, Rq)
- rq_can_notate :: Dots -> [Rq] -> Bool
- rq_to_seconds_qpm :: Fractional a => a -> a -> a
- rq_to_qpm :: Fractional a => a -> a -> a
Documentation
rq_tuplet_duration_table :: [(Rq, Duration)] Source #
Table mapping tuple Rq values to Durations. Only has cases where the duration can be expressed without a tie. Currently has entries for 3-,5-,6- and 7-tuplets.
all (\(i,j) -> i == duration_to_rq j) rq_tuplet_duration_table == True
rq_tuplet_to_duration :: Rq -> Maybe Duration Source #
Lookup rq_tuplet_duration_tbl.
rq_tuplet_to_duration (1/3) == Just (Duration 8 0 (2/3))
rq_plain_duration_tbl :: Dots -> [(Rq, Duration)] Source #
Make table of (Rq,Duration) associations. Only lists durations with a multiplier of 1.
map (length . rq_plain_duration_tbl) [1,2,3] == [20,30,40] map (multiplier . snd) (rq_plain_duration_tbl 1) == replicate 20 1
rq_to_duration :: Dots -> Rq -> Maybe Duration Source #
Rational quarter note to duration value.
     Lookup composite plain (hence dots) and tuplet tables.
     It is a mistake to hope this could handle tuplets directly in a general sense.
     For instance, a 3:2 dotted note is the same duration as a plain undotted note.
     However it does give durations for simple notations of simple tuplet values.
rq_to_duration 2 (3/4) == Just (Duration 8 1 1) -- dotted_eighth_note rq_to_duration 2 (1/3) == Just (Duration 8 0 (2/3))
rq_to_duration_err :: Show a => a -> Dots -> Rq -> Duration Source #
Variant of rq_to_duration with error message.
rq_is_cmn :: Dots -> Rq -> Bool Source #
Is Rq a cmn duration (ie. rq_plain_to_duration)
map (rq_is_cmn 2) [1/4,1/5,1/8,3/32] == [True,False,True,True]
whole_note_division_to_rq :: Division -> Rq Source #
Convert a whole note division integer to an Rq value.
map whole_note_division_to_rq [1,2,4,8] == [4,2,1,1/2]
rq_apply_dots :: Rq -> Dots -> Rq Source #
Apply dots to an Rq duration.
map (rq_apply_dots 1) [1,2] == [1 + 1/2,1 + 1/2 + 1/4]
duration_to_rq :: Duration -> Rq Source #
Convert Duration to Rq value, see rq_to_duration for partial inverse.
let d = [Duration 2 0 1,Duration 4 1 1,Duration 1 1 1] map duration_to_rq d == [2,3/2,6] -- half_note,dotted_quarter_note,dotted_whole_note
duration_compare_rq :: Duration -> Duration -> Ordering Source #
compare function for Duration via duration_to_rq.
half_note `duration_compare_rq` quarter_note == GT
rq_divisible_by :: Rq -> Rq -> Bool Source #
Is p divisible by q, ie. is the denominator of p/q == 1.
map (rq_divisible_by (3%2)) [1%2,1%3] == [True,False]
rq_is_integral :: Rq -> Bool Source #
Is Rq a whole number (ie. is denominator == 1.
map rq_is_integral [1,3/2,2] == [True,False,True]
rq_integral :: Rq -> Maybe Integer Source #
Return numerator of Rq if denominator == 1.
map rq_integral [1,3/2,2] == [Just 1,Nothing,Just 2]
rq_derive_tuplet_plain :: [Rq] -> Maybe (Integer, Integer) Source #
Derive the tuplet structure of a set of Rq values.
rq_derive_tuplet_plain [1/2] == Nothing rq_derive_tuplet_plain [1/2,1/2] == Nothing rq_derive_tuplet_plain [1/4,1/4] == Nothing rq_derive_tuplet_plain [1/3,2/3] == Just (3,2) rq_derive_tuplet_plain [1/2,1/3,1/6] == Just (6,4) rq_derive_tuplet_plain [1/3,1/6] == Just (6,4) rq_derive_tuplet_plain [2/5,3/5] == Just (5,4) rq_derive_tuplet_plain [1/3,1/6,2/5,1/10] == Just (30,16)
map rq_derive_tuplet_plain [[1/3,1/6],[2/5,1/10]] == [Just (6,4)
                                                     ,Just (10,8)]rq_derive_tuplet :: [Rq] -> Maybe (Integer, Integer) Source #
Derive the tuplet structure of a set of Rq values.
rq_derive_tuplet [1/4,1/8,1/8] == Nothing rq_derive_tuplet [1/3,2/3] == Just (3,2) rq_derive_tuplet [1/2,1/3,1/6] == Just (3,2) rq_derive_tuplet [2/5,3/5] == Just (5,4) rq_derive_tuplet [1/3,1/6,2/5,1/10] == Just (15,8)
rq_un_tuplet :: (Integer, Integer) -> Rq -> Rq Source #
Remove tuplet multiplier from value, ie. to give notated
 duration.  This seems odd but is neccessary to avoid ambiguity.
 Ie. is 1 a quarter note or a 3:2 tuplet dotted-quarter-note etc.
map (rq_un_tuplet (3,2)) [1,2/3,1/2,1/3] == [3/2,1,3/4,1/2]
rq_to_cmn :: Rq -> Maybe (Rq, Rq) Source #
If an Rq duration is un-representable by a single cmn
 duration, give tied notation.
catMaybes (map rq_to_cmn [1..9]) == [(4,1),(4,3),(8,1)]
map rq_to_cmn [5/4,5/8] == [Just (1,1/4),Just (1/2,1/8)]
rq_can_notate :: Dots -> [Rq] -> Bool Source #
Predicate to determine if a segment can be notated either without a tuplet or with a single tuplet.
rq_can_notate 2 [1/2,1/4,1/4] == True rq_can_notate 2 [1/3,1/6] == True rq_can_notate 2 [2/5,1/10] == True rq_can_notate 2 [1/3,1/6,2/5,1/10] == False rq_can_notate 2 [4/7,1/7,6/7,3/7] == True rq_can_notate 2 [4/7,1/7,2/7] == True
Time
rq_to_seconds_qpm :: Fractional a => a -> a -> a Source #
Duration in seconds of Rq given qpm
qpm = pulses-per-minute, rq = rational-quarter-note
map (\sd -> rq_to_seconds_qpm (90 * sd) 1) [1,2,4,8,16] == [2/3,1/3,1/6,1/12,1/24] map (rq_to_seconds_qpm 90) [1,2,3,4] == [2/3,1 + 1/3,2,2 + 2/3] map (rq_to_seconds_qpm 90) [0::Rq,1,1 + 1/2,1 + 3/4,1 + 7/8,2] == [0,2/3,1,7/6,5/4,4/3]
rq_to_qpm :: Fractional a => a -> a -> a Source #
Qpm given that rq has duration x, ie. inverse of rq_to_seconds_qpm
map (rq_to_qpm 1) [0.4,0.5,0.8,1,1.5,2] == [150,120,75,60,40,30] map (\qpm -> rq_to_seconds_qpm qpm 1) [150,120,75,60,40,30] == [0.4,0.5,0.8,1,1.5,2]