hmt-0.16: Haskell Music Theory

Safe HaskellSafe
LanguageHaskell98

Music.Theory.Pitch.Note

Contents

Description

Common music notation note and alteration values.

Synopsis

Note_T

data Note_T Source #

Enumeration of common music notation note names (C to B).

Constructors

C 
D 
E 
F 
G 
A 
B 

note_seq :: [Note_T] Source #

Note sequence as usually understood, ie. C - B.

note_pp :: Note_T -> Char Source #

Char variant of show.

note_pc_tbl :: Num i => [(Note_T, i)] Source #

Table of Note_T and corresponding pitch-classes.

note_to_pc :: Num i => Note_T -> i Source #

Transform Note_T to pitch-class number.

map note_to_pc [C,E,G] == [0,4,7]

pc_to_note :: (Eq i, Num i) => i -> Maybe Note_T Source #

Inverse of note_to_pc.

mapMaybe pc_to_note [0,4,7] == [C,E,G]

note_t_transpose :: Note_T -> Int -> Note_T Source #

Modal transposition of Note_T value.

note_t_transpose C 2 == E

parse_note_t :: Bool -> Char -> Maybe Note_T Source #

Parser from Char, case insensitive flag.

mapMaybe (parse_note True) "CDEFGab" == [C,D,E,F,G,A,B]

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 == []

Alteration

alteration_to_diff :: Alteration_T -> Maybe Int Source #

Transform Alteration_T to semitone alteration. Returns Nothing for non-semitone alterations.

map alteration_to_diff [Flat,QuarterToneSharp] == [Just (-1),Nothing]

alteration_to_diff_err :: Integral i => Alteration_T -> i Source #

Transform Alteration_T to semitone alteration.

map alteration_to_diff_err [Flat,Sharp] == [-1,1]

alteration_to_fdiff :: Fractional n => Alteration_T -> n Source #

Transform Alteration_T to fractional semitone alteration, ie. allow quarter tones.

alteration_to_fdiff QuarterToneSharp == 0.5

fdiff_to_alteration :: (Fractional n, Eq n) => n -> Maybe Alteration_T Source #

Transform fractional semitone alteration to Alteration_T, ie. allow quarter tones.

map fdiff_to_alteration [-0.5,0.5] == [Just QuarterToneFlat
                                      ,Just QuarterToneSharp]

alteration_raise_quarter_tone :: Alteration_T -> Maybe Alteration_T Source #

Raise Alteration_T by a quarter tone where possible.

alteration_raise_quarter_tone Flat == Just QuarterToneFlat
alteration_raise_quarter_tone DoubleSharp == Nothing

alteration_lower_quarter_tone :: Alteration_T -> Maybe Alteration_T Source #

Lower Alteration_T by a quarter tone where possible.

alteration_lower_quarter_tone Sharp == Just QuarterToneSharp
alteration_lower_quarter_tone DoubleFlat == Nothing

alteration_edit_quarter_tone :: (Fractional n, Eq n) => n -> Alteration_T -> Maybe Alteration_T Source #

Edit Alteration_T by a quarter tone where possible, -0.5 lowers, 0 retains, 0.5 raises.

import Data.Ratio
alteration_edit_quarter_tone (-1 % 2) Flat == Just ThreeQuarterToneFlat

alteration_clear_quarter_tone :: Alteration_T -> Alteration_T Source #

Simplify Alteration_T to standard 12ET by deleting quarter tones.

Data.List.nub (map alteration_clear_quarter_tone [minBound..maxBound])

alteration_symbol :: Alteration_T -> Char Source #

Unicode has entries for Musical Symbols in the range U+1D100 through U+1D1FF. The 3/4 symbols are non-standard, here they correspond to MUSICAL SYMBOL FLAT DOWN and MUSICAL SYMBOL SHARP UP.

map alteration_symbol [minBound .. maxBound] == "𝄫𝄭♭𝄳♮𝄲♯𝄰𝄪"

symbol_to_alteration :: Char -> Maybe Alteration_T Source #

Inverse of alteration_symbol.

mapMaybe symbol_to_alteration "♭♮♯" == [Flat,Natural,Sharp]

symbol_to_alteration_iso :: Char -> Maybe Alteration_T Source #

Variant of symbol_to_alteration that also recognises b for Flat and # for Sharp and x for double sharp.

alteration_iso_m :: Alteration_T -> Maybe String Source #

The ISO ASCII spellings for alterations. Naturals are written as the empty string.

mapMaybe alteration_iso_m [Flat .. Sharp] == ["b","","#"]
mapMaybe alteration_iso_m [DoubleFlat,DoubleSharp] == ["bb","x"]

alteration_iso :: Alteration_T -> String Source #

The ISO ASCII spellings for alterations.

alteration_tonh :: Alteration_T -> String Source #

The Tonhöhe ASCII spellings for alterations.

See http://www.musiccog.ohio-state.edu/Humdrum/guide04.html and http://lilypond.org/doc/v2.16/Documentation/notation/writing-pitches

map alteration_tonh [Flat .. Sharp] == ["es","eh","","ih","is"]

12-ET

note_alteration_ks :: [(Note_T, Alteration_T)] Source #

Note & alteration sequence in key-signature spelling.

pc_note_alteration_ks_tbl :: Integral i => [((Note_T, Alteration_T), i)] Source #

Table connecting pitch class number with note_alteration_ks.

Rational Alteration

type Alteration_R = (Rational, String) Source #

Alteration given as a rational semitone difference and a string representation of the alteration.

alteration_r :: Alteration_T -> Alteration_R Source #

Transform Alteration_T to Alteration_R.

let r = [(-1,"♭"),(0,"♮"),(1,"♯")]
in map alteration_t' [Flat,Natural,Sharp] == r