hmt-0.15: Haskell Music Theory

Safe HaskellSafe-Inferred
LanguageHaskell98

Music.Theory.Pitch

Contents

Description

Common music notation pitch values.

Synopsis

Documentation

type PitchClass = Int Source

Pitch classes are modulo twelve integers.

type Octave = Int Source

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

type Octave_PitchClass i = (i, i) Source

Octave and PitchClass duple.

data Pitch Source

Common music notation pitch value.

Constructors

Pitch 

Instances

data Pitch' Source

Generalised pitch, given by a generalised alteration.

Instances

pitch'_pp :: Pitch' -> String Source

Pretty printer for Pitch'.

pitch'_class_pp :: Pitch' -> String Source

Pitch' printed without octave.

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

pitch_to_pc (Pitch A Natural 4) == 9
pitch_to_pc (Pitch F Sharp 4) == 6

pitch_compare :: Pitch -> Pitch -> Ordering Source

Pitch comparison, implemented via pitch_to_fmidi.

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

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

Given Spelling function translate from OctPC notation to Pitch.

octpc_nrm :: Integral i => Octave_PitchClass i -> Octave_PitchClass i Source

Normalise OctPC value, ie. ensure PitchClass is in (0,11).

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

octpc_trs :: Integral i => i -> Octave_PitchClass i -> Octave_PitchClass i Source

Transpose OctPC value.

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

octpc_to_midi :: Integral i => Octave_PitchClass i -> i Source

OctPC value to integral midi note number.

octpc_to_midi (4,9) == 69

midi_to_octpc :: Integral i => i -> Octave_PitchClass i Source

Inverse of octpc_to_midi.

midi_to_octpc 69 == (4,9)

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_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_to_pitch :: RealFrac n => Spelling Int -> n -> Pitch Source

Fractional midi note number to Pitch.

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

pitch_tranpose :: RealFrac 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

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 :: (Integral i, Floating f) => i -> f Source

Midi note number to cycles per second.

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

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

Fractional midi note number to cycles per second.

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

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]

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

Frequency (cycles per second) to fractional midi note number.

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

type Midi_Detune = (Int, Double) Source

Midi note number with cents detune.

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)]

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

midi_to_cps of octpc_to_midi.

octpc_to_cps (4,9) == 440

Parsers

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 :: Pitch -> String Source

Pretty printer for Pitch (unicode, see alteration_symbol).

pitch_pp (Pitch E Flat 4) == "E♭4"
pitch_pp (Pitch F QuarterToneSharp 3) == "F𝄲3"

pitch_class_pp :: Pitch -> String Source

Pitch printed without octave.

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

Sequential list of n pitch class names starting from k.

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_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"