hmt-0.16: Haskell Music Theory

Safe HaskellSafe
LanguageHaskell98

Music.Theory.Time_Signature

Contents

Description

Time Signatures.

Synopsis

Documentation

type Time_Signature = (Integer, Integer) Source #

A Time Signature is a (numerator,denominator) pair.

ts_whole_note :: Time_Signature -> [Duration] Source #

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

ts_whole_note (3,8) == [dotted_quarter_note]
ts_whole_note (2,2) == [whole_note]

ts_whole_note_rq :: Time_Signature -> RQ Source #

Duration of measure in RQ.

map ts_whole_note_rq [(3,8),(2,2)] == [3/2,4]

ts_rq :: Time_Signature -> RQ Source #

Duration, in RQ, of a measure of indicated Time_Signature.

map ts_rq [(3,4),(5,8)] == [3,5/2]

rq_to_ts :: RQ -> Time_Signature Source #

Time_Signature derived from whole note duration in RQ form.

map rq_to_ts [4,3/2,7/4,6] == [(4,4),(3,8),(7,16),(6,4)]

ts_divisions :: Time_Signature -> [RQ] Source #

Uniform division of time signature.

ts_divisions (3,4) == [1,1,1]
ts_divisions (3,8) == [1/2,1/2,1/2]
ts_divisions (2,2) == [2,2]
ts_divisions (1,1) == [4]
ts_divisions (7,4) == [1,1,1,1,1,1,1]

ts_duration_pulses :: Time_Signature -> Duration -> Rational Source #

Convert a duration to a pulse count in relation to the indicated time signature.

ts_duration_pulses (3,8) quarter_note == 2

ts_rewrite :: Integer -> Time_Signature -> Time_Signature Source #

Rewrite time signature to indicated denominator.

ts_rewrite 8 (3,4) == (6,8)

ts_sum :: [Time_Signature] -> Time_Signature Source #

Sum time signatures.

ts_sum [(3,16),(1,2)] == (11,16)

Composite Time Signatures

type Composite_Time_Signature = [Time_Signature] Source #

A composite time signature is a sequence of Time_Signatures.

cts_rq :: Composite_Time_Signature -> RQ Source #

The RQ is the sum of ts_rq of the elements.

cts_rq [(3,4),(1,8)] == 3 + 1/2

cts_divisions :: Composite_Time_Signature -> [RQ] Source #

The divisions are the concat of the ts_divisions of the elements.

cts_divisions [(3,4),(1,8)] == [1,1,1,1/2]

cts_pulse_to_rq :: Composite_Time_Signature -> Int -> RQ Source #

Pulses are 1-indexed, RQ locations are 0-indexed.

map (cts_pulse_to_rq [(2,4),(1,8),(1,4)]) [1 .. 4] == [0,1,2,2 + 1/2]

cts_pulse_to_rqw :: Composite_Time_Signature -> Int -> (RQ, RQ) Source #

Variant that gives the window of the pulse (ie. the start location and the duration).

let r = [(0,1),(1,1),(2,1/2),(2 + 1/2,1)]
in map (cts_pulse_to_rqw [(2,4),(1,8),(1,4)]) [1 .. 4] == r

Rational Time Signatures

type Rational_Time_Signature = [(Rational, Rational)] Source #

A rational time signature is a Composite_Time_Signature where the parts are Rational.

rts_rq :: Rational_Time_Signature -> RQ Source #

The sum of the RQ of the elements.

rts_rq [(3,4),(1,8)] == 3 + 1/2
rts_rq [(3/2,4),(1/2,8)] == 3/2 + 1/4

rts_divisions :: Rational_Time_Signature -> [[RQ]] Source #

The divisions of the elements.

rts_divisions [(3,4),(1,8)] == [1,1,1,1/2]
rts_divisions [(3/2,4),(1/2,8)] == [1,1/2,1/4]

rts_pulse_to_rq :: Rational_Time_Signature -> Int -> RQ Source #

Pulses are 1-indexed, RQ locations are 0-indexed.

map (rts_pulse_to_rq [(2,4),(1,8),(1,4)]) [1 .. 4] == [0,1,2,2 + 1/2]
map (rts_pulse_to_rq [(3/2,4),(1/2,8),(1/4,4)]) [1 .. 4] == [0,1,3/2,7/4]

rts_pulse_to_rqw :: Rational_Time_Signature -> Int -> (RQ, RQ) Source #

Variant that gives the window of the pulse (ie. the start location and the duration).

let r = [(0,1),(1,1),(2,1/2),(2 + 1/2,1)]
in map (rts_pulse_to_rqw [(2,4),(1,8),(1,4)]) [1 .. 4] == r