hmt-0.20: Haskell Music Theory
Safe HaskellSafe-Inferred
LanguageHaskell2010

Music.Theory.Pitch.Note

Description

Common music notation note and alteration values.

Synopsis

Note

data Note Source #

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

Constructors

C 
D 
E 
F 
G 
A 
B 

Instances

Instances details
Bounded Note Source # 
Instance details

Defined in Music.Theory.Pitch.Note

Enum Note Source # 
Instance details

Defined in Music.Theory.Pitch.Note

Methods

succ :: Note -> Note #

pred :: Note -> Note #

toEnum :: Int -> Note #

fromEnum :: Note -> Int #

enumFrom :: Note -> [Note] #

enumFromThen :: Note -> Note -> [Note] #

enumFromTo :: Note -> Note -> [Note] #

enumFromThenTo :: Note -> Note -> Note -> [Note] #

Read Note Source # 
Instance details

Defined in Music.Theory.Pitch.Note

Show Note Source # 
Instance details

Defined in Music.Theory.Pitch.Note

Methods

showsPrec :: Int -> Note -> ShowS #

show :: Note -> String #

showList :: [Note] -> ShowS #

Eq Note Source # 
Instance details

Defined in Music.Theory.Pitch.Note

Methods

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

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

Ord Note Source # 
Instance details

Defined in Music.Theory.Pitch.Note

Methods

compare :: Note -> Note -> Ordering #

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

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

(>) :: Note -> Note -> Bool #

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

max :: Note -> Note -> Note #

min :: Note -> Note -> Note #

note_seq :: [Note] Source #

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

note_pp :: Note -> Char Source #

Char variant of show.

note_pp_ly :: Note -> String Source #

Note name in lilypond syntax (ie. lower case).

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

Table of Note and corresponding pitch-classes.

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

Transform Note to pitch-class number.

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

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

Inverse of note_to_pc.

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

note_t_transpose :: Note -> Int -> Note Source #

Modal transposition of Note value.

note_t_transpose C 2 == E

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

Parser from Char, case insensitive flag.

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

note_span :: Note -> Note -> [Note] Source #

Inclusive set of Note 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

data Alteration Source #

Enumeration of common music notation note alterations.

alteration_to_diff :: Alteration -> Maybe Int Source #

Transform Alteration 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 -> i Source #

Transform Alteration to semitone alteration.

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

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

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

alteration_to_fdiff QuarterToneSharp == 0.5

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

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

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

alteration_raise_quarter_tone :: Alteration -> Maybe Alteration Source #

Raise Alteration by a quarter tone where possible.

alteration_raise_quarter_tone Flat == Just QuarterToneFlat
alteration_raise_quarter_tone DoubleSharp == Nothing

alteration_lower_quarter_tone :: Alteration -> Maybe Alteration Source #

Lower Alteration 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 -> Maybe Alteration Source #

Edit Alteration 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 -> Alteration Source #

Simplify Alteration to standard 12ET by deleting quarter tones.

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

alteration_symbol_tbl :: [(Alteration, Char)] Source #

Table of Unicode characters for alterations.

alteration_symbol :: Alteration -> 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 Source #

Inverse of alteration_symbol.

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

symbol_to_alteration_iso :: Bool -> String -> Maybe Alteration Source #

ISO alteration notation. When not strict extended to allow ## for x.

symbol_to_alteration_unicode_plus_iso :: Char -> Maybe Alteration Source #

symbol_to_alteration extended to allow single character ISO notations.

alteration_iso_tbl :: [(Alteration, String)] Source #

ISO alteration table, strings not characters because of double flat.

alteration_iso_m :: Alteration -> 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 -> String Source #

The ISO ASCII spellings for alterations.

alteration_tonh_tbl :: [(Alteration, String)] Source #

The Tonhöhe ASCII spellings for alterations.

alteration_tonh :: Alteration -> 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"]

tonh_to_alteration :: String -> Maybe Alteration Source #

Inverse of alteration_tonh.

mapMaybe tonh_to_alteration ["es","eh","","ih","is"] == [Flat .. Sharp]

12-ET

note_alteration_to_pc :: (Note, Alteration) -> Maybe Int Source #

Note and alteration to pitch-class, or not.

note_alteration_to_pc_err :: (Note, Alteration) -> Int Source #

Error variant.

map note_alteration_to_pc_err [(A,DoubleSharp),(B,Sharp),(C,Flat),(C,DoubleFlat)]

note_alteration_ks :: [(Note, Alteration)] Source #

Note & alteration sequence in key-signature spelling.

pc_note_alteration_ks_tbl :: Integral i => [((Note, Alteration), 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 -> Alteration_R Source #

Transform Alteration to Alteration_R.

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

Parsers

p_note_t :: P Note Source #

Parser for ISO note name, upper case.

map (T.run_parser_error p_note_t . return) "ABCDEFG"

p_note_t_lc :: P Note Source #

Note name in lower case (not ISO)

p_note_t_ci :: P Note Source #

Case-insensitive note name (not ISO).

p_alteration_t_iso :: Bool -> P Alteration Source #

Parser for ISO alteration name.

map (T.run_parser_error p_alteration_t_iso) (words "bb b # x ##")