hmt-0.16: Haskell Music Theory

Safe HaskellSafe
LanguageHaskell98

Music.Theory.Pitch

Contents

Description

Common music notation pitch values.

Synopsis

Octave & pitch-class (generic)

type Octave_PitchClass i = (i, i) Source #

Octave and PitchClass duple.

octave_pitchclass_nrm :: Integral i => Octave_PitchClass i -> Octave_PitchClass i Source #

Normalise Octave_PitchClass value, ie. ensure pitch-class is in (0,11).

octave_pitchclass_to_midi :: Integral i => Octave_PitchClass i -> i Source #

Octave_PitchClass value to integral midi note number.

Octave & PitchClass

type PitchClass = Int Source #

Pitch classes are modulo twelve integers.

type Octave = Int Source #

Octaves are integers, the octave of middle C is 4.

to_octpc :: (Integral pc, Integral oct) => (oct, pc) -> OctPC Source #

Translate from generic octave & pitch-class duple.

octpc_nrm :: OctPC -> OctPC Source #

Normalise OctPC.

octpc_nrm (4,16) == (5,4)

octpc_trs :: Int -> OctPC -> OctPC Source #

Transpose OctPC.

octpc_trs 7 (4,9) == (5,4)
octpc_trs (-11) (4,9) == (3,10)

octpc_range :: (OctPC, OctPC) -> [OctPC] Source #

Enumerate range, inclusive.

octpc_range ((3,8),(4,1)) == [(3,8),(3,9),(3,10),(3,11),(4,0),(4,1)]

Midi note number

type Midi = Int Source #

Midi note number

octpc_to_midi :: OctPC -> Midi Source #

OctPC value to integral midi note number.

map octpc_to_midi [(0,0),(2,6),(4,9),(9,0)] == [12,42,69,120]
map octpc_to_midi [(0,9),(8,0)] == [21,108]

midi_to_octpc :: Midi -> OctPC Source #

Inverse of octpc_to_midi.

map midi_to_octpc [40,69] == [(2,4),(4,9)]

Octave & fractional pitch-class

type FMidi = Double Source #

Fractional midi note number.

type FOctPC = (Int, Double) Source #

Fractional octave pitch-class (octave is integral, pitch-class is fractional).

fmidi_to_foctpc :: RealFrac f => f -> (Octave, f) Source #

Fractional midi to fractional octave pitch-class.

fmidi_to_foctpc 69.5 == (4,9.5)

fmidi_octave :: RealFrac f => f -> Octave Source #

Octave of fractional midi note number.

fmidi_in_octave :: RealFrac f => Octave -> f -> f Source #

Move fractional midi note number to indicated octave.

map (fmidi_in_octave 1) [59.5,60.5] == [35.5,24.5]

Pitch

data Pitch Source #

Common music notation pitch value.

Constructors

Pitch 

Instances

Eq Pitch Source # 

Methods

(==) :: Pitch -> Pitch -> Bool #

(/=) :: Pitch -> Pitch -> Bool #

Ord Pitch Source # 

Methods

compare :: Pitch -> Pitch -> Ordering #

(<) :: Pitch -> Pitch -> Bool #

(<=) :: Pitch -> Pitch -> Bool #

(>) :: Pitch -> Pitch -> Bool #

(>=) :: Pitch -> Pitch -> Bool #

max :: Pitch -> Pitch -> Pitch #

min :: Pitch -> Pitch -> Pitch #

Show Pitch Source # 

Methods

showsPrec :: Int -> Pitch -> ShowS #

show :: Pitch -> String #

showList :: [Pitch] -> ShowS #

pitch_clear_quarter_tone :: Pitch -> Pitch Source #

Simplify Pitch to standard 12ET by deleting quarter tones.

let p = Pitch A QuarterToneSharp 4
in alteration (pitch_clear_quarter_tone p) == Sharp

pitch_to_octpc :: Integral i => Pitch -> Octave_PitchClass i Source #

Pitch to Octave and PitchClass notation.

pitch_to_octpc (Pitch F Sharp 4) == (4,6)

pitch_to_midi :: Integral i => Pitch -> i Source #

Pitch to midi note number notation.

pitch_to_midi (Pitch A Natural 4) == 69

pitch_to_fmidi :: Fractional n => Pitch -> n Source #

Pitch to fractional midi note number notation.

pitch_to_fmidi (Pitch A QuarterToneSharp 4) == 69.5

pitch_to_pc :: Pitch -> PitchClass Source #

Extract PitchClass of Pitch

map pitch_to_pc [Pitch A Natural 4,Pitch F Sharp 4] == [9,6]
map pitch_to_pc [Pitch C Flat 4,Pitch B Sharp 5] == [11,0]

pitch_compare :: Pitch -> Pitch -> Ordering Source #

Pitch comparison, implemented via pitch_to_fmidi.

pitch_compare (Pitch A Natural 4) (Pitch A QuarterToneSharp 4) == LT

Spelling

type Spelling n = n -> (Note_T, Alteration_T) Source #

Function to spell a PitchClass.

type Spelling_M i = i -> Maybe (Note_T, Alteration_T) Source #

Variant of Spelling for incomplete functions.

octpc_to_pitch :: Integral i => Spelling i -> Octave_PitchClass i -> Pitch Source #

Given Spelling function translate from OctPC notation to Pitch.

octpc_to_pitch T.pc_spell_sharp (4,6) == Pitch T.F T.Sharp 4

midi_to_pitch :: Integral i => Spelling i -> i -> Pitch Source #

Midi note number to Pitch.

let r = ["C4","E♭4","F♯4"]
in map (pitch_pp . midi_to_pitch pc_spell_ks) [60,63,66] == r

fmidi_et12_cents_pp :: Spelling PitchClass -> Double -> String Source #

Print fractional midi note number as ET12 pitch with cents detune in parentheses.

fmidi_et12_cents_pp 66.5 == "F♯4(+50)"

fmidi_to_pitch :: RealFrac n => Spelling PitchClass -> n -> Maybe Pitch Source #

Fractional midi note number to Pitch.

fmidi_to_pitch pc_spell_ks 69.25 == Nothing

fmidi_to_pitch_err :: (Show n, RealFrac n) => Spelling Int -> n -> Pitch Source #

Erroring variant.

import Music.Theory.Pitch.Spelling
pitch_pp (fmidi_to_pitch_err pc_spell_ks 65.5) == "F𝄲4"
pitch_pp (fmidi_to_pitch_err pc_spell_ks 66.5) == "F𝄰4"
pitch_pp (fmidi_to_pitch_err pc_spell_ks 67.5) == "A𝄭4"
pitch_pp (fmidi_to_pitch_err pc_spell_ks 69.5) == "B𝄭4"

pitch_tranpose :: (RealFrac n, Show n) => Spelling Int -> n -> Pitch -> Pitch Source #

Composition of pitch_to_fmidi and then fmidi_to_pitch.

import Music.Theory.Pitch.Name as T
import Music.Theory.Pitch.Spelling as T
pitch_tranpose T.pc_spell_ks 2 T.ees5 == T.f5

fmidi_in_octave_of :: RealFrac f => f -> f -> f Source #

Displacement of q into octave of p.

fmidi_in_octave_nearest :: RealFrac n => n -> n -> n Source #

Octave displacement of m2 that is nearest m1.

let {p = octpc_to_fmidi (2,1);q = map octpc_to_fmidi [(4,11),(4,0),(4,1)]}
in map (fmidi_in_octave_nearest p) q == [35,36,37]

fmidi_in_octave_above :: RealFrac a => a -> a -> a Source #

Displacement of q into octave above p.

fmidi_in_octave_of 69 51 == 63
fmidi_in_octave_nearest 69 51 == 63
fmidi_in_octave_above 69 51 == 75

fmidi_in_octave_below :: RealFrac a => a -> a -> a Source #

Displacement of q into octave below p.

fmidi_in_octave_of 69 85 == 61
fmidi_in_octave_nearest 69 85 == 73
fmidi_in_octave_below 69 85 == 61

cps_in_octave' :: Floating f => (f -> f -> f) -> f -> f -> f Source #

cps_in_octave_nearest :: (Floating f, RealFrac f) => f -> f -> f Source #

CPS form of fmidi_in_octave_nearest.

map cps_octave [440,256] == [4,4]
round (cps_in_octave_nearest 440 256) == 512

cps_in_octave_above :: (Ord a, Fractional a) => a -> a -> a Source #

Raise or lower the frequency q by octaves until it is in the octave starting at p.

cps_in_octave_above 55.0 392.0 == 98.0

cps_in_octave_above' :: (Floating f, RealFrac f) => f -> f -> f Source #

cps_in_octave_below :: (Floating f, RealFrac f) => f -> f -> f Source #

pitch_in_octave_nearest :: Pitch -> Pitch -> Pitch Source #

Set octave of p2 so that it nearest to p1.

import Music.Theory.Pitch.Name as T
let {r = ["B1","C2","C#2"];f = pitch_in_octave_nearest T.cis2}
in map (pitch_pp_iso . f) [T.b4,T.c4,T.cis4] == r

pitch_note_raise :: Pitch -> Pitch Source #

Raise Note_T of Pitch, account for octave transposition.

pitch_note_raise (Pitch B Natural 3) == Pitch C Natural 4

pitch_note_lower :: Pitch -> Pitch Source #

Lower Note_T of Pitch, account for octave transposition.

pitch_note_lower (Pitch C Flat 4) == Pitch B Flat 3

pitch_rewrite_threequarter_alteration :: Pitch -> Pitch Source #

Rewrite Pitch to not use 3/4 tone alterations, ie. re-spell to 1/4 alteration.

let {p = Pitch A ThreeQuarterToneFlat 4
    ;q = Pitch G QuarterToneSharp 4}
in pitch_rewrite_threequarter_alteration p == q

pitch_edit_octave :: (Octave -> Octave) -> Pitch -> Pitch Source #

Apply function to octave of PitchClass.

pitch_edit_octave (+ 1) (Pitch A Natural 4) == Pitch A Natural 5

Frequency (CPS)

midi_to_cps_f0 :: (Integral i, Floating f) => f -> i -> f Source #

Midi note number to cycles per second, given frequency of ISO A4.

midi_to_cps :: (Integral i, Floating f) => i -> f Source #

midi_to_cps_f0 440.

map midi_to_cps [60,69] == [261.6255653005986,440.0]

fmidi_to_cps_f0 :: Floating a => a -> a -> a Source #

Fractional midi note number to cycles per second, given frequency of ISO A4.

fmidi_to_cps :: Floating a => a -> a Source #

fmidi_to_cps_f0 440.

map fmidi_to_cps [69,69.1] == [440.0,442.5488940698553]

pitch_to_cps_f0 :: Floating n => n -> Pitch -> n Source #

fmidi_to_cps of pitch_to_fmidi, given frequency of ISO A4.

cps_to_fmidi_f0 :: Floating a => a -> a -> a Source #

Frequency (cps = cycles per second) to fractional midi note number, given frequency of ISO A4 (mnn = 69).

cps_to_fmidi :: Floating a => a -> a Source #

cps_to_fmidi_f0 440.

cps_to_fmidi 440 == 69
cps_to_fmidi (fmidi_to_cps 60.25) == 60.25

cps_to_midi :: (Integral i, Floating f, RealFrac f) => f -> i Source #

Frequency (cycles per second) to midi note number, ie. round of cps_to_fmidi.

map cps_to_midi [261.6,440] == [60,69]

octpc_to_cps_f0 :: (Integral i, Floating n) => n -> Octave_PitchClass i -> n Source #

midi_to_cps_f0 of octpc_to_midi, given frequency of ISO A4.

octpc_to_cps :: (Integral i, Floating n) => Octave_PitchClass i -> n Source #

octpc_to_cps_f0 440.

octpc_to_cps (4,9) == 440

MIDI detune (cents)

type Midi_Detune' c = (Int, c) Source #

Midi note number with cents detune.

cents_is_normal :: (Num c, Ord c) => c -> Bool Source #

Is cents in (-50,+50].

map cents_is_normal [-250,-75,75,250] == replicate 4 False

midi_detune_normalise :: (Ord c, Num c) => Midi_Detune' c -> Midi_Detune' c Source #

In normal form the detune is in the range (-50,+50] instead of [0,100) or wider.

map midi_detune_normalise [(60,-250),(60,-75),(60,75),(60,250)]

midi_detune_to_cps_f0 :: Real c => Double -> Midi_Detune' c -> Double Source #

Inverse of cps_to_midi_detune, given frequency of ISO A4.

midi_detune_to_cps :: Real c => Midi_Detune' c -> Double Source #

Inverse of cps_to_midi_detune.

map midi_detune_to_cps [(69,0),(68,100)] == [440,440]

midi_detune_to_fmidi :: Real c => Midi_Detune' c -> Double Source #

Midi_Detune to fractional midi note number.

midi_detune_to_fmidi (60,50.0) == 60.50

midi_detune_to_pitch :: Real c => Spelling Int -> Midi_Detune' c -> Pitch Source #

Midi_Detune to Pitch, detune must be precisely at a notateable Pitch.

let p = Pitch {note = C, alteration = QuarterToneSharp, octave = 4}
in midi_detune_to_pitch T.pc_spell_ks (midi_detune_nearest_24et (60,35)) == p

type Midi_Detune = Midi_Detune' Double Source #

Midi note number with real-valued cents detune.

fmidi_to_midi_detune :: Double -> Midi_Detune Source #

Fractional midi note number to Midi_Detune.

fmidi_to_midi_detune 60.50 == (60,50.0)

cps_to_midi_detune :: Double -> Midi_Detune Source #

Frequency (in hertz) to Midi_Detune.

map (fmap round . cps_to_midi_detune) [440.00,508.35] == [(69,0),(71,50)]

midi_detune_nearest_24et :: Midi_Detune -> Midi_Detune Source #

Round detune value to nearest multiple of 50, normalised.

map midi_detune_nearest_24et [(59,70),(59,80)] == [(59,50),(60,00)]

MIDI cents

type Midi_Cents = Midi_Detune' Int Source #

Midi note number with integral cents detune.

midi_cents_pp :: Midi_Cents -> String Source #

Printed as fmidi value with cents to two places. Must be normal.

map midi_cents_pp [(60,0),(60,25)] == ["60.00","60.25"]

Parsers

parse_octave :: Num a => a -> String -> Maybe a Source #

Parse possible octave from single integer.

map (parse_octave 2) ["","4","x","11"]

parse_iso_pitch_oct :: Octave -> String -> Maybe Pitch Source #

Slight generalisation of ISO pitch representation. Allows octave to be elided, pitch names to be lower case, and double sharps written as ##.

See http://www.musiccog.ohio-state.edu/Humdrum/guide04.html

let r = [Pitch C Natural 4,Pitch A Flat 5,Pitch F DoubleSharp 6]
in mapMaybe (parse_iso_pitch_oct 4) ["C","Ab5","f##6",""] == r

parse_iso_pitch :: String -> Maybe Pitch Source #

Variant of parse_iso_pitch_oct requiring octave.

Pretty printers

pitch_pp_opt :: (Bool, Bool) -> Pitch -> String Source #

Pretty printer for Pitch (unicode, see alteration_symbol). Option selects if Naturals are printed.

pitch_pp_opt (True,True) (Pitch T.E T.Natural 4) == "E♮4"

pitch_pp :: Pitch -> String Source #

pitch_pp_opt with default options, ie. (False,True).

pitch_pp (Pitch T.E T.Natural 4) == "E4"
pitch_pp (Pitch T.E T.Flat 4) == "E♭4"
pitch_pp (Pitch T.F T.QuarterToneSharp 3) == "F𝄲3"

pitch_class_pp :: Pitch -> String Source #

pitch_pp_opt with options (False,False).

pitch_class_pp (Pitch T.C T.ThreeQuarterToneSharp 0) == "C𝄰"

pitch_class_names_12et :: Integral n => Spelling n -> n -> n -> [String] Source #

Sequential list of n pitch class names starting from k.

unwords (pitch_class_names_12et 0 12) == "C C♯ D E♭ E F F♯ G A♭ A B♭ B"
pitch_class_names_12et 11 2 == ["B","C"]

pitch_pp_iso :: Pitch -> String Source #

Pretty printer for Pitch (ISO, ASCII, see alteration_iso).

pitch_pp_iso (Pitch E Flat 4) == "Eb4"
pitch_pp_iso (Pitch F DoubleSharp 3) == "Fx3"
pitch_pp_iso (Pitch C ThreeQuarterToneSharp 4) -- error

pitch_pp_hly :: Pitch -> String Source #

Pretty printer for Pitch (ASCII, see alteration_tonh).

pitch_pp_hly (Pitch E Flat 4) == "ees4"
pitch_pp_hly (Pitch F QuarterToneSharp 3) == "fih3"
pitch_pp_hly (Pitch B Natural 6) == "b6"

pitch_pp_tonh :: Pitch -> String Source #

Pretty printer for Pitch (Tonhöhe, see alteration_tonh).

pitch_pp_tonh (Pitch E Flat 4) == "Es4"
pitch_pp_tonh (Pitch F QuarterToneSharp 3) == "Fih3"
pitch_pp_tonh (Pitch B Natural 6) == "H6"

24ET

pc24et_to_pitch :: Integral i => i -> Pitch Source #

genericIndex into pc24et_univ.

pitch_class_pp (pc24et_to_pitch 13) == "F𝄰"

Pitch, rational alteration.

data Pitch_R Source #

Generalised pitch, given by a generalised alteration.

pitch_r_pp :: Pitch_R -> String Source #

Pretty printer for Pitch_R.

pitch_r_class_pp :: Pitch_R -> String Source #

Pitch_R printed without octave.