HarmTrace-Base-1.6.0.0: Parsing and unambiguously representing musical chords.

Copyright(c) 2012--2016 Chordify BV
LicenseLGPL-3
Maintainerhaskelldevelopers@chordify.net
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

HarmTrace.Base.Chord.Datatypes

Contents

Description

Summary: A set of types and classes for representing musical chords. The chord datatypes are based on the unambiguous chord representation presented in: Christopher Harte, Mark Sandler and Samer Abdallah (2005), Symbolic representation of musical chords: a proposed syntax for text annotations, In: Proceedings of 6th International Conference on Music Information Retrieval (http://ismir2005.ismir.net/proceedings/1080.pdf).

Synopsis

Representing musical chords and keys

data Note a Source #

A musical note is a pitch (either absolute or relative) possibly modified by an Accidental

Constructors

Note Accidental a 

Instances

Show ChordLabel Source # 
EnHarEq ChordLabel Source # 
Eq a => Eq (Note a) Source # 

Methods

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

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

Ord a => Ord (Note a) Source # 

Methods

compare :: Note a -> Note a -> Ordering #

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

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

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

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

max :: Note a -> Note a -> Note a #

min :: Note a -> Note a -> Note a #

Read (Note DiatonicNatural) Source # 
Show (Note IntNat) Source # 
Show (Note DiatonicNatural) Source # 
Show (Note DiatonicDegree) Source # 
Generic (Note a) Source # 

Associated Types

type Rep (Note a) :: * -> * #

Methods

from :: Note a -> Rep (Note a) x #

to :: Rep (Note a) x -> Note a #

Binary a => Binary (Note a) Source # 

Methods

put :: Note a -> Put #

get :: Get (Note a) #

putList :: [Note a] -> Put #

Diatonic a => EnHarEq (Note a) Source # 

Methods

(&==) :: Note a -> Note a -> Bool Source #

(&/=) :: Note a -> Note a -> Bool Source #

type Rep (Note a) Source # 
type Rep (Note a) = D1 (MetaData "Note" "HarmTrace.Base.Chord.Datatypes" "HarmTrace-Base-1.6.0.0-BLvMBN84kkFFjgsWeov2oZ" False) (C1 (MetaCons "Note" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Accidental)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))))

data Accidental Source #

A musical Accidental

Constructors

Nat

natural

Sh

sharp

Fl

flat

SS

double sharp

FF

double flat

type Root = Note DiatonicNatural Source #

Representing absolute Root notes

data DiatonicNatural Source #

The seven diatonic naturals

Constructors

C 
D 
E 
F 
G 
A 
B 

Instances

Bounded DiatonicNatural Source # 
Enum DiatonicNatural Source # 
Eq DiatonicNatural Source # 
Ord DiatonicNatural Source # 
Read DiatonicNatural Source # 
Show DiatonicNatural Source # 
Show ChordLabel Source # 
Generic DiatonicNatural Source # 
Binary DiatonicNatural Source # 
Diatonic DiatonicNatural Source # 
EnHarEq ChordLabel Source # 
Read (Note DiatonicNatural) Source # 
Show (Note DiatonicNatural) Source # 
type Rep DiatonicNatural Source # 
type Rep DiatonicNatural = D1 (MetaData "DiatonicNatural" "HarmTrace.Base.Chord.Datatypes" "HarmTrace-Base-1.6.0.0-BLvMBN84kkFFjgsWeov2oZ" False) ((:+:) ((:+:) (C1 (MetaCons "C" PrefixI False) U1) ((:+:) (C1 (MetaCons "D" PrefixI False) U1) (C1 (MetaCons "E" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "F" PrefixI False) U1) (C1 (MetaCons "G" PrefixI False) U1)) ((:+:) (C1 (MetaCons "A" PrefixI False) U1) (C1 (MetaCons "B" PrefixI False) U1))))

type ScaleDegree = Note DiatonicDegree Source #

Key relative scale degrees to abstract from the absolute Root notes

data DiatonicDegree Source #

All Diatonic scale degrees

Constructors

I 
II 
III 
IV 
V 
VI 
VII 
Imp

for unrepresentable scale degrees

Instances

Bounded DiatonicDegree Source # 
Enum DiatonicDegree Source # 
Eq DiatonicDegree Source # 
Ord DiatonicDegree Source # 
Show DiatonicDegree Source # 
Generic DiatonicDegree Source # 

Associated Types

type Rep DiatonicDegree :: * -> * #

Binary DiatonicDegree Source # 
Diatonic DiatonicDegree Source # 
Show (Note DiatonicDegree) Source # 
type Rep DiatonicDegree Source # 
type Rep DiatonicDegree = D1 (MetaData "DiatonicDegree" "HarmTrace.Base.Chord.Datatypes" "HarmTrace-Base-1.6.0.0-BLvMBN84kkFFjgsWeov2oZ" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "I" PrefixI False) U1) (C1 (MetaCons "II" PrefixI False) U1)) ((:+:) (C1 (MetaCons "III" PrefixI False) U1) (C1 (MetaCons "IV" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "V" PrefixI False) U1) (C1 (MetaCons "VI" PrefixI False) U1)) ((:+:) (C1 (MetaCons "VII" PrefixI False) U1) (C1 (MetaCons "Imp" PrefixI False) U1))))

Keys

data Key Source #

A musical key consising of a Root and Mode

Constructors

Key 

Fields

Instances

Eq Key Source # 

Methods

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

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

Ord Key Source # 

Methods

compare :: Key -> Key -> Ordering #

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

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

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Read Key Source # 
Show Key Source # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Binary Key Source # 

Methods

put :: Key -> Put #

get :: Get Key #

putList :: [Key] -> Put #

type Rep Key Source # 
type Rep Key = D1 (MetaData "Key" "HarmTrace.Base.Chord.Datatypes" "HarmTrace-Base-1.6.0.0-BLvMBN84kkFFjgsWeov2oZ" False) (C1 (MetaCons "Key" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "keyRoot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Root)) (S1 (MetaSel (Just Symbol "keyMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Mode))))

data Mode Source #

The Mode of a key, which can be major or minor

Constructors

MajMode 
MinMode 

Instances

Eq Mode Source # 

Methods

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

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

Ord Mode Source # 

Methods

compare :: Mode -> Mode -> Ordering #

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

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

(>) :: Mode -> Mode -> Bool #

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

max :: Mode -> Mode -> Mode #

min :: Mode -> Mode -> Mode #

Read Mode Source # 
Show Mode Source # 

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Generic Mode Source # 

Associated Types

type Rep Mode :: * -> * #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

Binary Mode Source # 

Methods

put :: Mode -> Put #

get :: Get Mode #

putList :: [Mode] -> Put #

type Rep Mode Source # 
type Rep Mode = D1 (MetaData "Mode" "HarmTrace.Base.Chord.Datatypes" "HarmTrace-Base-1.6.0.0-BLvMBN84kkFFjgsWeov2oZ" False) ((:+:) (C1 (MetaCons "MajMode" PrefixI False) U1) (C1 (MetaCons "MinMode" PrefixI False) U1))

Chords

data Chord a Source #

The representation for a single chord consisting of a root, a Shorthand representing the interval structure of the chord, a list of Additions, for representing other (additional) structure, and the base Inversion

Constructors

Chord a Shorthand [Addition] Interval

a regular chord

NoChord

No sounding chord (silence, noise, etc.)

UndefChord

An undefined chord

Instances

Functor Chord Source # 

Methods

fmap :: (a -> b) -> Chord a -> Chord b #

(<$) :: a -> Chord b -> Chord a #

Show ChordLabel Source # 
EnHarEq ChordLabel Source # 
Eq a => Eq (Chord a) Source # 

Methods

(==) :: Chord a -> Chord a -> Bool #

(/=) :: Chord a -> Chord a -> Bool #

Ord a => Ord (Chord a) Source # 

Methods

compare :: Chord a -> Chord a -> Ordering #

(<) :: Chord a -> Chord a -> Bool #

(<=) :: Chord a -> Chord a -> Bool #

(>) :: Chord a -> Chord a -> Bool #

(>=) :: Chord a -> Chord a -> Bool #

max :: Chord a -> Chord a -> Chord a #

min :: Chord a -> Chord a -> Chord a #

Generic (Chord a) Source # 

Associated Types

type Rep (Chord a) :: * -> * #

Methods

from :: Chord a -> Rep (Chord a) x #

to :: Rep (Chord a) x -> Chord a #

Binary a => Binary (Chord a) Source # 

Methods

put :: Chord a -> Put #

get :: Get (Chord a) #

putList :: [Chord a] -> Put #

type Rep (Chord a) Source # 

chordRoot :: Show a => Chord a -> a Source #

Returns the root of a Chord, and throws an error in case of a NoChord or an UndefChord.

chordShorthand :: Show a => Chord a -> Shorthand Source #

Returns the Shorthand of a Chord, and throws an error in case of a NoChord or an UndefChord.

chordAdditions :: Show a => Chord a -> [Addition] Source #

Returns the list of Additions of a Chord, and throws an error in case of a NoChord or an UndefChord.

chordBass :: Show a => Chord a -> Interval Source #

Returns the bass Interval of a Chord, and throws an error in case of a NoChord or an UndefChord.

data Shorthand Source #

Following Harte et al., we define a number of chord Shorthands. We support a few extra shorthand, but the show intance of Shorthand will only output the Shorthands that are in the official specification

Constructors

Maj

Triadic chords

Min 
Dim 
Aug 
Maj7

Seventh chords

Min7 
Sev 
Dim7 
HDim7 
MinMaj7 
Aug7 
Maj6

Sixth chords

Min6 
Nin

Extended chords

Maj9 
Min9 
Sus4

Suspended chords

Sus2 
SevSus4 
Five

Power chords

None

Only a root note

Eleven

Additional shorthands in billboard collection

Thirteen 
Min11 
Maj13 
Min13 

Instances

Bounded Shorthand Source # 
Enum Shorthand Source # 
Eq Shorthand Source # 
Ord Shorthand Source # 
Show Shorthand Source # 
Generic Shorthand Source # 

Associated Types

type Rep Shorthand :: * -> * #

Binary Shorthand Source # 
type Rep Shorthand Source # 
type Rep Shorthand = D1 (MetaData "Shorthand" "HarmTrace.Base.Chord.Datatypes" "HarmTrace-Base-1.6.0.0-BLvMBN84kkFFjgsWeov2oZ" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Maj" PrefixI False) U1) ((:+:) (C1 (MetaCons "Min" PrefixI False) U1) (C1 (MetaCons "Dim" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Aug" PrefixI False) U1) ((:+:) (C1 (MetaCons "Maj7" PrefixI False) U1) (C1 (MetaCons "Min7" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Sev" PrefixI False) U1) ((:+:) (C1 (MetaCons "Dim7" PrefixI False) U1) (C1 (MetaCons "HDim7" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "MinMaj7" PrefixI False) U1) (C1 (MetaCons "Aug7" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Maj6" PrefixI False) U1) (C1 (MetaCons "Min6" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Nin" PrefixI False) U1) ((:+:) (C1 (MetaCons "Maj9" PrefixI False) U1) (C1 (MetaCons "Min9" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Sus4" PrefixI False) U1) ((:+:) (C1 (MetaCons "Sus2" PrefixI False) U1) (C1 (MetaCons "SevSus4" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Five" PrefixI False) U1) ((:+:) (C1 (MetaCons "None" PrefixI False) U1) (C1 (MetaCons "Eleven" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Thirteen" PrefixI False) U1) (C1 (MetaCons "Min11" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Maj13" PrefixI False) U1) (C1 (MetaCons "Min13" PrefixI False) U1))))))

data Addition Source #

Intervals for additional chord notes

Constructors

Add Interval 
NoAdd Interval 

data IntNat Source #

Diatonic major intervals used to denote Chord Additions and bass Intervals

Constructors

I1 
I2 
I3 
I4 
I5 
I6 
I7 
I8 
I9 
I10 
I11 
I12 
I13 

Instances

Bounded IntNat Source # 
Enum IntNat Source # 
Eq IntNat Source # 

Methods

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

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

Ord IntNat Source # 
Show IntNat Source # 
Generic IntNat Source # 

Associated Types

type Rep IntNat :: * -> * #

Methods

from :: IntNat -> Rep IntNat x #

to :: Rep IntNat x -> IntNat #

Binary IntNat Source # 

Methods

put :: IntNat -> Put #

get :: Get IntNat #

putList :: [IntNat] -> Put #

Show (Note IntNat) Source # 
type Rep IntNat Source # 
type Rep IntNat = D1 (MetaData "IntNat" "HarmTrace.Base.Chord.Datatypes" "HarmTrace-Base-1.6.0.0-BLvMBN84kkFFjgsWeov2oZ" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "I1" PrefixI False) U1) ((:+:) (C1 (MetaCons "I2" PrefixI False) U1) (C1 (MetaCons "I3" PrefixI False) U1))) ((:+:) (C1 (MetaCons "I4" PrefixI False) U1) ((:+:) (C1 (MetaCons "I5" PrefixI False) U1) (C1 (MetaCons "I6" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "I7" PrefixI False) U1) ((:+:) (C1 (MetaCons "I8" PrefixI False) U1) (C1 (MetaCons "I9" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "I10" PrefixI False) U1) (C1 (MetaCons "I11" PrefixI False) U1)) ((:+:) (C1 (MetaCons "I12" PrefixI False) U1) (C1 (MetaCons "I13" PrefixI False) U1)))))

type ChordLabel = Chord Root Source #

A chord based on absolute Root notes

type ChordDegree = Chord ScaleDegree Source #

A chord based on relative ScaleDegrees

Derived types for classification of chords

data ClassType Source #

Updates the root field of a Chord updateRoot :: Chord a -> a -> Chord a updateRoot (Chord r sh a b) r' = Chord r' sh a b

We introduce four chord categories: major chords, minor chords, dominant seventh chords, and diminished seventh chords

Instances

Bounded ClassType Source # 
Enum ClassType Source # 
Eq ClassType Source # 
Ord ClassType Source # 
Show ClassType Source # 
Generic ClassType Source # 

Associated Types

type Rep ClassType :: * -> * #

Binary ClassType Source # 
type Rep ClassType Source # 
type Rep ClassType = D1 (MetaData "ClassType" "HarmTrace.Base.Chord.Datatypes" "HarmTrace-Base-1.6.0.0-BLvMBN84kkFFjgsWeov2oZ" False) ((:+:) ((:+:) (C1 (MetaCons "MajClass" PrefixI False) U1) (C1 (MetaCons "MinClass" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DomClass" PrefixI False) U1) ((:+:) (C1 (MetaCons "DimClass" PrefixI False) U1) (C1 (MetaCons "NoClass" PrefixI False) U1))))

data Triad Source #

A Triad comes in four flavours: major, minor, augmented, diminished, and sometimes a chord does not have a triad (e.g. suspended chords, etc.)

Instances

Eq Triad Source # 

Methods

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

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

Ord Triad Source # 

Methods

compare :: Triad -> Triad -> Ordering #

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

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

(>) :: Triad -> Triad -> Bool #

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

max :: Triad -> Triad -> Triad #

min :: Triad -> Triad -> Triad #

Show Triad Source # 

Methods

showsPrec :: Int -> Triad -> ShowS #

show :: Triad -> String #

showList :: [Triad] -> ShowS #

Generic Triad Source # 

Associated Types

type Rep Triad :: * -> * #

Methods

from :: Triad -> Rep Triad x #

to :: Rep Triad x -> Triad #

Binary Triad Source # 

Methods

put :: Triad -> Put #

get :: Get Triad #

putList :: [Triad] -> Put #

type Rep Triad Source # 
type Rep Triad = D1 (MetaData "Triad" "HarmTrace.Base.Chord.Datatypes" "HarmTrace-Base-1.6.0.0-BLvMBN84kkFFjgsWeov2oZ" False) ((:+:) ((:+:) (C1 (MetaCons "MajTriad" PrefixI False) U1) (C1 (MetaCons "MinTriad" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AugTriad" PrefixI False) U1) ((:+:) (C1 (MetaCons "DimTriad" PrefixI False) U1) (C1 (MetaCons "NoTriad" PrefixI False) U1))))

Tests & Utilities

shortChord :: Root -> Shorthand -> ChordLabel Source #

A Constructor for a simple chord based on a Root and Shorthand only

discardBass :: Chord a -> Chord a Source #

Discards a base note by replacing the bass Interval by a Note Nat I1

addition :: Chord a -> Addition -> Chord a Source #

Adds an Addition to a Chord

insertAdd :: [Addition] -> Addition -> [Addition] Source #

Applies an Addition to a list of Additions

isNoneChord :: ChordLabel -> Bool Source #

Returns True if the ChordLabel is not a chord, and False otherwise

isAddition :: Addition -> Bool Source #

Returns true if the Chord Addition represents an addition and not a degree that has to be removed (*).

catchNoChord :: Show a => String -> (Chord a -> b) -> Chord a -> b Source #

Checks if the ChordLabel is a NoChord or UndefChord and throws an error using the first argument as an function identifier for debugging. In case of a ChordLabel the second argument is applied to the third argument.