hmt-0.15: Haskell Music Theory

Safe HaskellSafe-Inferred
LanguageHaskell98

Music.Theory.Interval

Description

Common music notation intervals.

Synopsis

Documentation

data Interval Source

Common music notation interval. An Ordering of LT indicates an ascending interval, GT a descending interval, and EQ a unison.

Instances

interval_ty :: Note_T -> Note_T -> Interval_T Source

Interval type between Note_T values.

map (interval_ty C) [E,B] == [Third,Seventh]

interval_q_tbl :: Integral n => [(Interval_T, [(n, Interval_Q)])] Source

Table of interval qualities. For each Interval_T gives directed semitone interval counts for each allowable Interval_Q. For lookup function see interval_q, for reverse lookup see interval_q_reverse.

interval_q :: Interval_T -> Int -> Maybe Interval_Q Source

Lookup Interval_Q for given Interval_T and semitone count.

interval_q Unison 11 == Just Diminished
interval_q Third 5 == Just Augmented
interval_q Fourth 5 == Just Perfect
interval_q Unison 3 == Nothing

interval_q_reverse :: Interval_T -> Interval_Q -> Maybe Int Source

Lookup semitone difference of Interval_T with Interval_Q.

interval_q_reverse Third Minor == Just 3
interval_q_reverse Unison Diminished == Just 11

interval_semitones :: Interval -> Int Source

Semitone difference of Interval.

interval_semitones (interval (Pitch C Sharp 4) (Pitch E Sharp 5)) == 16
interval_semitones (interval (Pitch C Natural 4) (Pitch D Sharp 3)) == -9

note_span :: Note_T -> Note_T -> [Note_T] Source

Inclusive set of Note_T within indicated interval. This is not equal to enumFromTo which is not circular.

note_span E B == [E,F,G,A,B]
note_span B D == [B,C,D]
enumFromTo B D == []

invert_ordering :: Ordering -> Ordering Source

Invert Ordering, ie. GT becomes LT and vice versa.

map invert_ordering [LT,EQ,GT] == [GT,EQ,LT]

interval :: Pitch -> Pitch -> Interval Source

Determine Interval between two Pitches.

interval (Pitch C Sharp 4) (Pitch D Flat 4) == Interval Second Diminished EQ 0
interval (Pitch C Sharp 4) (Pitch E Sharp 5) == Interval Third Major LT 1

invert_interval :: Interval -> Interval Source

Apply invert_ordering to interval_direction of Interval.

invert_interval (Interval Third Major LT 1) == Interval Third Major GT 1

quality_difference_m :: Interval_Q -> Interval_Q -> Maybe Int Source

The signed difference in semitones between two Interval_Q values when applied to the same Interval_T. Can this be written correctly without knowing the Interval_T?

quality_difference_m Minor Augmented == Just 2
quality_difference_m Augmented Diminished == Just (-3)
quality_difference_m Major Perfect == Nothing

pitch_transpose :: Interval -> Pitch -> Pitch Source

Transpose a Pitch by an Interval.

transpose (Interval Third Diminished LT 0) (Pitch C Sharp 4) == Pitch E Flat 4

circle_of_fifths :: Pitch -> ([Pitch], [Pitch]) Source

Make leftwards (perfect fourth) and and rightwards (perfect fifth) circles from Pitch.

let c = circle_of_fifths (Pitch F Sharp 4)
in map pitch_to_pc (snd c) == [6,1,8,3,10,5,12,7,2,9,4,11]

parse_interval_type :: String -> Maybe (Interval_T, Octave) Source

Parse a positive integer into interval type and octave displacement.

mapMaybe parse_interval_type (map show [1 .. 15])

parse_interval_quality :: Char -> Maybe Interval_Q Source

Parse interval quality notation.

mapMaybe parse_interval_quality "dmPMA" == [minBound .. maxBound]

interval_type_degree :: (Interval_T, Octave) -> Int Source

Degree of interval type and octave displacement. Inverse of parse_interval_type.

map interval_type_degree [(Third,0),(Second,1),(Unison,2)] == [3,9,15]

interval_quality_pp :: Interval_Q -> Char Source

Inverse of 'parse_interval_quality.

parse_interval :: String -> Maybe Interval Source

Parse standard common music interval notation.

let i = mapMaybe parse_interval (words "P1 d2 m2 M2 A3 P8 +M9 -M2")
in unwords (map interval_pp i) == "P1 d2 m2 M2 A3 P8 M9 -M2"
mapMaybe (fmap interval_octave . parse_interval) (words "d1 d8 d15") == [-1,0,1]

interval_pp :: Interval -> String Source

Pretty printer for intervals, inverse of parse_interval.

std_interval_names :: ([String], [String]) Source

Standard names for the intervals within the octave, divided into perfect, major and minor at the left, and diminished and augmented at the right.

let {bimap f (p,q) = (f p,f q)
    ;f = mapMaybe (fmap interval_semitones . parse_interval)}
in bimap f std_interval_names