Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Common music notation pitch values.
Synopsis
- type Octave_PitchClass i = (i, i)
- octave_pitchclass_nrm :: (Ord i, Num i) => Octave_PitchClass i -> Octave_PitchClass i
- octave_pitchclass_trs :: Integral i => i -> Octave_PitchClass i -> Octave_PitchClass i
- octave_pitchclass_to_midi :: Num i => Octave_PitchClass i -> i
- midi_to_octave_pitchclass :: (Integral m, Integral i) => m -> Octave_PitchClass i
- pianokey_to_octave_pitchclass :: (Integral m, Integral i) => m -> Octave_PitchClass i
- type PitchClass = Int
- type Octave = Int
- type OctPc = (Octave, PitchClass)
- octave_pitchclass_to_octpc :: (Integral pc, Integral oct) => (oct, pc) -> OctPc
- octpc_nrm :: OctPc -> OctPc
- octpc_trs :: Int -> OctPc -> OctPc
- octpc_range :: (OctPc, OctPc) -> [OctPc]
- type Midi = Int
- midi_to_int :: Midi -> Int
- double_to_midi :: (Double -> Midi) -> Double -> Midi
- octpc_to_midi :: OctPc -> Midi
- midi_to_octpc :: Midi -> OctPc
- octpc_to_foct :: (Integral i, Fractional r) => (i, i) -> r
- foct_to_octpc :: (Integral i, RealFrac r) => r -> (i, i)
- foct_to_midi :: (Integral i, RealFrac r) => r -> i
- type FMidi = Double
- type FOctPc = (Int, Double)
- octpc_to_fmidi :: (Integral i, Num n) => Octave_PitchClass i -> n
- fmidi_to_foctpc :: RealFrac f => f -> (Octave, f)
- fmidi_octave :: RealFrac f => f -> Octave
- foctpc_to_fmidi :: RealFrac f => (Octave, f) -> f
- fmidi_in_octave :: RealFrac f => Octave -> f -> f
- fmidi_et12_cents_pp :: Spelling PitchClass -> FMidi -> String
- data Pitch = Pitch {
- note :: Note
- alteration :: Alteration
- octave :: Octave
- pitch_clear_quarter_tone :: Pitch -> Pitch
- pitch_to_octpc :: Integral i => Pitch -> Octave_PitchClass i
- pitch_is_12et :: Pitch -> Bool
- pitch_to_midi :: Integral i => Pitch -> i
- pitch_to_fmidi :: Fractional n => Pitch -> n
- pitch_to_pc :: Pitch -> PitchClass
- pitch_compare :: Pitch -> Pitch -> Ordering
- type Spelling n = n -> (Note, Alteration)
- type Spelling_M i = i -> Maybe (Note, Alteration)
- octpc_to_pitch :: Integral i => Spelling i -> Octave_PitchClass i -> Pitch
- midi_to_pitch :: (Integral i, Integral k) => Spelling k -> i -> Pitch
- fmidi_to_pitch :: RealFrac n => Spelling PitchClass -> n -> Maybe Pitch
- fmidi_to_pitch_err :: (Show n, RealFrac n) => Spelling Int -> n -> Pitch
- pitch_transpose_fmidi :: (RealFrac n, Show n) => Spelling Int -> n -> Pitch -> Pitch
- fmidi_in_octave_of :: RealFrac f => f -> f -> f
- fmidi_in_octave_nearest :: RealFrac n => n -> n -> n
- fmidi_in_octave_above :: RealFrac a => a -> a -> a
- fmidi_in_octave_below :: RealFrac a => a -> a -> a
- lift_fmidi_binop_to_cps :: Floating f => (f -> f -> f) -> f -> f -> f
- cps_in_octave_nearest :: (Floating f, RealFrac f) => f -> f -> f
- cps_in_octave_above :: (Floating f, RealFrac f) => f -> f -> f
- cps_in_octave_below :: (Floating f, RealFrac f) => f -> f -> f
- cps_in_octave_above_direct :: (Ord a, Fractional a) => a -> a -> a
- pitch_in_octave_nearest :: Pitch -> Pitch -> Pitch
- pitch_note_raise :: Pitch -> Pitch
- pitch_note_lower :: Pitch -> Pitch
- pitch_rewrite_threequarter_alteration :: Pitch -> Pitch
- pitch_edit_octave :: (Octave -> Octave) -> Pitch -> Pitch
- pitch_to_cps_k0 :: Floating n => (n, n) -> Pitch -> n
- pitch_to_cps_f0 :: Floating n => n -> Pitch -> n
- pitch_to_cps :: Floating n => Pitch -> n
- cps_to_fmidi_k0 :: Floating a => (a, a) -> a -> a
- cps_to_fmidi :: Floating a => a -> a
- cps_to_midi :: (Integral i, Floating f, RealFrac f) => f -> i
- octpc_to_cps_k0 :: (Integral i, Floating n) => (n, n) -> Octave_PitchClass i -> n
- octpc_to_cps :: (Integral i, Floating n) => Octave_PitchClass i -> n
- cps_to_octpc :: (Floating f, RealFrac f, Integral i) => f -> Octave_PitchClass i
- cps_octave :: (Floating f, RealFrac f) => f -> Octave
- cents_is_normal :: (Num c, Ord c) => c -> Bool
- midi_detune_is_normal :: (Num c, Ord c) => (x, c) -> Bool
- midi_detune_normalise :: (Num m, Ord c, Num c) => (m, c) -> (m, c)
- midi_detune_normalise_positive :: (Num m, Ord m, Ord c, Num c) => (m, c) -> (m, c)
- midi_detune_to_cps_f0 :: (Integral m, Real c) => Double -> (m, c) -> Double
- midi_detune_to_cps :: (Integral m, Real c) => (m, c) -> Double
- midi_detune_to_fmidi :: (Integral m, Real c) => (m, c) -> Double
- midi_detune_to_pitch :: (Integral m, Real c) => Spelling Int -> (m, c) -> Pitch
- type Midi_Detune = (Midi, Double)
- fmidi_to_midi_detune :: Double -> Midi_Detune
- cps_to_midi_detune :: Double -> Midi_Detune
- midi_detune_nearest_24et :: Midi_Detune -> Midi_Detune
- type Midi_Cents = (Midi, Int)
- midi_detune_to_midi_cents :: Midi_Detune -> Midi_Cents
- midi_cents_pp :: Midi_Cents -> String
- pc24et_univ :: [Pitch]
- pc24et_to_pitch :: Integral i => i -> Pitch
- data Pitch_R = Pitch_R Note Alteration_R Octave
- pitch_r_pp :: Pitch_R -> String
- pitch_r_class_pp :: Pitch_R -> String
- p_octave_iso :: P Octave
- p_octave_iso_opt :: Octave -> P Octave
- p_iso_pitch_strict :: P Pitch
- p_iso_pitch_oct :: Octave -> P Pitch
- parse_octave :: Octave -> String -> Octave
- parse_iso_pitch_oct :: Octave -> String -> Maybe Pitch
- parse_iso_pitch :: String -> Maybe Pitch
- parse_iso_pitch_err :: String -> Pitch
- pitch_pp_opt :: (Bool, Bool) -> Pitch -> String
- pitch_pp :: Pitch -> String
- pitch_class_pp :: Pitch -> String
- pitch_class_names_12et :: Integral n => Spelling n -> n -> n -> [String]
- pitch_pp_iso :: Pitch -> String
- ly_octave_tbl :: [(Octave, String)]
- octave_pp_ly :: Octave -> String
- octave_parse_ly :: String -> Maybe Octave
- pitch_pp_hly :: Pitch -> String
- pitch_pp_tonh :: Pitch -> String
- p_octave_ly :: P Octave
- p_pitch_ly :: P Pitch
- pitch_parse_ly_err :: String -> Pitch
- p_pitch_hly :: P Pitch
- pitch_parse_hly :: String -> Pitch
Octave pitch-class (generic)
type Octave_PitchClass i = (i, i) Source #
Octave
and PitchClass
duple.
octave_pitchclass_nrm :: (Ord i, Num i) => Octave_PitchClass i -> Octave_PitchClass i Source #
Normalise Octave_PitchClass
value, ie. ensure pitch-class is in (0,11).
octave_pitchclass_trs :: Integral i => i -> Octave_PitchClass i -> Octave_PitchClass i Source #
Transpose Octave_PitchClass
value.
octave_pitchclass_to_midi :: Num i => Octave_PitchClass i -> i Source #
Octave_PitchClass
value to integral midi note number.
map octave_pitchclass_to_midi [(-1,9),(8,0)] == map (+ 9) [0,99]
midi_to_octave_pitchclass :: (Integral m, Integral i) => m -> Octave_PitchClass i Source #
Inverse of octave_pitchclass_to_midi
.
map midi_to_octave_pitchclass [0,36,60,84,91] == [(-1,0),(2,0),(4,0),(6,0),(6,7)]
pianokey_to_octave_pitchclass :: (Integral m, Integral i) => m -> Octave_PitchClass i Source #
One-indexed piano key number (for standard 88 key piano) to pitch class. This has the mnemonic that 49 maps to (4,9).
map pianokey_to_octave_pitchclass [1,49,88] == [(0,9),(4,9),(8,0)]
Octave & PitchClass
type PitchClass = Int Source #
Pitch classes are modulo twelve integers (0-11)
type OctPc = (Octave, PitchClass) Source #
Octave
and PitchClass
duple.
octave_pitchclass_to_octpc :: (Integral pc, Integral oct) => (oct, pc) -> OctPc Source #
Translate from generic octave & pitch-class duple.
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 (0 - 127)
Midi note number (0 - 127). Midi data values are unsigned 7-bit integers, however using an unsigned type would be problematic. It would make transposition, for instance, awkward. x - 12 would transpose down an octave, but the transposition interval itself could not be negative.
midi_to_int :: Midi -> Int Source #
Type conversion
double_to_midi :: (Double -> Midi) -> Double -> Midi Source #
Type-specialise f, ie. round, ceiling, truncate
octpc_to_midi :: OctPc -> Midi Source #
OctPc
value to integral midi note number.
map octpc_to_midi [(0,0),(2,6),(4,9),(6,2),(9,0)] == [12,42,69,86,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
octpc_to_foct :: (Integral i, Fractional r) => (i, i) -> r Source #
(octave,pitch-class) to fractional octave.
This is an odd notation, but can be useful for writing pitch data where a float is required.
Note this is not a linear octave, for that see oct_to_cps
.
map octpc_to_foct [(4,0),(4,7),(5,11)] == [4.00,4.07,5.11]
foct_to_octpc :: (Integral i, RealFrac r) => r -> (i, i) Source #
Inverse of octpc_to_foct
.
map foct_to_octpc [3.11,4.00,4.07,5.11] == [(3,11),(4,0),(4,7),(5,11)]
foct_to_midi :: (Integral i, RealFrac r) => r -> i Source #
FMIDI
type FOctPc = (Int, Double) Source #
Fractional octave pitch-class (octave is integral, pitch-class is fractional).
octpc_to_fmidi :: (Integral i, Num n) => Octave_PitchClass i -> n Source #
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.
foctpc_to_fmidi :: RealFrac f => (Octave, f) -> f Source #
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]
fmidi_et12_cents_pp :: Spelling PitchClass -> FMidi -> String Source #
Print fractional midi note number as ET12 pitch with cents detune in parentheses.
fmidi_et12_cents_pp T.pc_spell_ks 66.5 == "F♯4(+50)"
Pitch
Common music notation pitch value.
Pitch | |
|
pitch_clear_quarter_tone :: Pitch -> Pitch Source #
Simplify Pitch
to standard 12ET by deleting quarter tones.
let p = Pitch T.A T.QuarterToneSharp 4 alteration (pitch_clear_quarter_tone p) == T.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, Alteration) Source #
Function to spell a PitchClass
.
type Spelling_M i = i -> Maybe (Note, Alteration) Source #
Variant of Spelling
for incomplete functions.
octpc_to_pitch :: Integral i => Spelling i -> Octave_PitchClass i -> Pitch Source #
midi_to_pitch :: (Integral i, Integral k) => Spelling k -> i -> Pitch Source #
Midi note number to Pitch
.
import Music.Theory.Pitch.Spelling.Table as T let r = ["C4","E♭4","F♯4"] map (pitch_pp . midi_to_pitch T.pc_spell_ks) [60,63,66] == r
fmidi_to_pitch :: RealFrac n => Spelling PitchClass -> n -> Maybe Pitch Source #
Fractional midi note number to Pitch
.
p = Pitch T.B T.ThreeQuarterToneFlat 4 map (fmidi_to_pitch T.pc_spell_ks) [69.25,69.5] == [Nothing,Just p]
fmidi_to_pitch_err :: (Show n, RealFrac n) => Spelling Int -> n -> Pitch Source #
Erroring variant.
import Music.Theory.Pitch.Spelling as T pitch_pp (fmidi_to_pitch_err T.pc_spell_ks 65.5) == "F𝄲4" pitch_pp (fmidi_to_pitch_err T.pc_spell_ks 66.5) == "F𝄰4" pitch_pp (fmidi_to_pitch_err T.pc_spell_ks 67.5) == "A𝄭4" pitch_pp (fmidi_to_pitch_err T.pc_spell_ks 69.5) == "B𝄭4"
pitch_transpose_fmidi :: (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_transpose_fmidi 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) let q = map octpc_to_fmidi [(4,11),(4,0),(4,1)] 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
lift_fmidi_binop_to_cps :: Floating f => (f -> f -> f) -> f -> f -> f Source #
CPS form of binary fmidi function f.
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 :: (Floating f, RealFrac f) => f -> f -> f Source #
CPS form of fmidi_in_octave_above
.
cps_in_octave_above 55.0 392.0 == 97.99999999999999
cps_in_octave_below :: (Floating f, RealFrac f) => f -> f -> f Source #
CPS form of fmidi_in_octave_above
.
cps_in_octave_above_direct :: (Ord a, Fractional a) => a -> a -> a Source #
Direct implementation of cps_in_octave_above
.
Raise or lower the frequency q by octaves until it is in the
octave starting at p.
cps_in_octave_above_direct 55.0 392.0 == 98.0
pitch_in_octave_nearest :: Pitch -> Pitch -> Pitch Source #
Set octave of p2 so that it nearest to p1.
import Music.Theory.Pitch import Music.Theory.Pitch.Name as T let r = ["B1","C2","C#2"] let f = pitch_in_octave_nearest T.cis2 map (pitch_pp_iso . f) [T.b4,T.c4,T.cis4] == r
pitch_note_raise :: Pitch -> Pitch Source #
Raise Note
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
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 T.A T.ThreeQuarterToneFlat 4 let q = Pitch T.G T.QuarterToneSharp 4 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 T.A T.Natural 4) == Pitch T.A T.Natural 5
Frequency (CPS)
pitch_to_cps_k0 :: Floating n => (n, n) -> Pitch -> n Source #
fmidi_to_cps
of pitch_to_fmidi
, given (k0,f0).
pitch_to_cps_f0 :: Floating n => n -> Pitch -> n Source #
fmidi_to_cps
of pitch_to_fmidi
, given frequency of ISO A4.
pitch_to_cps :: Floating n => Pitch -> n Source #
pitch_to_cps_k0
(60,440).
cps_to_fmidi_k0 :: Floating a => (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_k0
(69,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_k0 :: (Integral i, Floating n) => (n, n) -> Octave_PitchClass i -> n Source #
midi_to_cps_f0
of octpc_to_midi
, given (k0,f0)
octpc_to_cps :: (Integral i, Floating n) => Octave_PitchClass i -> n Source #
octpc_to_cps_k0
(69,440).
map (round . octpc_to_cps) [(-1,0),(0,0),(4,9),(9,0)] == [8,16,440,8372]
cps_to_octpc :: (Floating f, RealFrac f, Integral i) => f -> Octave_PitchClass i Source #
MIDI detune (cents)
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_is_normal :: (Num c, Ord c) => (x, c) -> Bool Source #
cents_is_normal
of snd
.
midi_detune_normalise :: (Num m, Ord c, Num c) => (m, c) -> (m, 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_normalise_positive :: (Num m, Ord m, Ord c, Num c) => (m, c) -> (m, c) Source #
In normal-positive form the detune is in the range (0,+100].
map midi_detune_normalise_positive [(60,-250),(60,-75),(60,75),(60,250)]
midi_detune_to_cps_f0 :: (Integral m, Real c) => Double -> (m, c) -> Double Source #
Inverse of cps_to_midi_detune
, given frequency of ISO A4
.
midi_detune_to_cps :: (Integral m, Real c) => (m, c) -> Double Source #
Inverse of cps_to_midi_detune
.
map midi_detune_to_cps [(69,0),(68,100)] == [440,440]
midi_detune_to_fmidi :: (Integral m, Real c) => (m, c) -> Double Source #
Midi_Detune
to fractional midi note number.
midi_detune_to_fmidi (60,50.0) == 60.50
midi_detune_to_pitch :: (Integral m, Real c) => Spelling Int -> (m, c) -> Pitch Source #
Midi_Detune
to Pitch
, detune must be precisely at a notateable Pitch.
let p = Pitch {note = T.C, alteration = T.QuarterToneSharp, octave = 4} midi_detune_to_pitch T.pc_spell_ks (midi_detune_nearest_24et (60,35)) == p
type Midi_Detune = (Midi, 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, 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"]
24ET
pc24et_univ :: [Pitch] Source #
The 24ET pitch-class universe, with sharp spellings, in octave '4'.
length pc24et_univ == 24
let r = "C C𝄲 C♯ C𝄰 D D𝄲 D♯ D𝄰 E E𝄲 F F𝄲 F♯ F𝄰 G G𝄲 G♯ G𝄰 A A𝄲 A♯ A𝄰 B B𝄲" unwords (map pitch_class_pp pc24et_univ) == r
pc24et_to_pitch :: Integral i => i -> Pitch Source #
genericIndex
into pc24et_univ
.
pitch_class_pp (pc24et_to_pitch 13) == "F𝄰"
Pitch, rational alteration.
Generalised pitch, given by a generalised alteration.
Parsers
p_octave_iso :: P Octave Source #
Parser for single digit ISO octave (C4 = middle-C)
p_octave_iso_opt :: Octave -> P Octave Source #
Parser for single digit ISO octave with default value in case of no parse.
p_iso_pitch_strict :: P Pitch Source #
Parser for ISO pitch notation.
parse_octave :: Octave -> String -> Octave Source #
Parse possible octave from single integer.
map (parse_octave 2) ["","4","x","11"] == [2,4,2,1]x
parse_iso_pitch_oct :: Octave -> String -> Maybe Pitch Source #
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 T.C T.Natural 4,Pitch T.A T.Flat 5,Pitch T.F T.DoubleSharp 6] 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 Natural
s 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.
import Music.Theory.Pitch.Spelling.Table unwords (pitch_class_names_12et pc_spell_ks 0 12) == "C C♯ D E♭ E F F♯ G A♭ A B♭ B" pitch_class_names_12et pc_spell_ks 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
ly_octave_tbl :: [(Octave, String)] Source #
Lilypond octave syntax.
octave_pp_ly :: Octave -> String Source #
Lookup ly_octave_tbl
.
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"
Parsers
p_octave_ly :: P Octave Source #
p_pitch_ly :: P Pitch Source #
pitch_parse_ly_err :: String -> Pitch Source #
Run p_pitch_ly
.
map (pitch_pp . pitch_parse_ly_err) ["c","d'","ees,","fisis''"] == ["C3","D4","E♭2","F𝄪5"]
p_pitch_hly :: P Pitch Source #
Parser for hly notation.
pitch_parse_hly :: String -> Pitch Source #
Run p_pitch_hly
.
map (pitch_pp . pitch_parse_hly) ["ees4","fih3","b6"] == ["E♭4","F𝄲3","B6"]