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

Portabilitynon-portable
Stabilityexperimental
Maintainerbash@cs.uu.nl, jpm@cs.ox.ac.uk
Safe HaskellSafe-Inferred

HarmTrace.Base.MusicRep

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 PieceLabel Source

A container type combinint a key and a list of ChordLabels

Constructors

PieceLabel Key [ChordLabel] 

data Note a Source

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

Constructors

Note (Maybe Accidental) a 

data Accidental Source

A musical Accidental

Constructors

Sh

sharp

Fl

flat

SS

double sharp

FF

double flat

type Root = Note DiatonicNaturalSource

Representing absolute Root notes

data DiatonicNatural Source

The seven diatonic naturals

Constructors

C 
D 
E 
F 
G 
A 
B 
N

for no root

X

for representing unknown roots (used in MIREX)

type ScaleDegree = Note DiatonicDegreeSource

Key relative scale degrees to abstract from the absolute Root notes

Keys

data Key Source

A musical key consising of a Root and Mode

Constructors

Key 

Fields

keyRoot :: Root
 
keyMode :: Mode
 

data Mode Source

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

Constructors

MajMode 
MinMode 

Chords

data Chord a Source

The representation for a single chord

Constructors

Chord 

Fields

chordRoot :: a
 
chordShorthand :: Shorthand
 
chordAdditions :: [Addition]
 
getLoc :: Int

the index of the chord in the list of tokens

duration :: Int

the duration of the chord

Instances

data Shorthand Source

Constructors

Maj

Triadic chords

Min 
Dim 
Aug 
Maj7

Seventh chords

Min7 
Sev 
Dim7 
HDim7 
MinMaj7 
Maj6

Sixth chords

Min6 
Nin

Extended chords

Maj9 
Min9 
Sus4

Suspended chords

Sus2 
Five

Power chords

None 
Eleven 
Thirteen 
Min11 
Maj13 
Min13 

data Addition Source

Intervals for additonal chord notes

Constructors

Add (Note Interval) 
NoAdd (Note Interval) 

data Interval Source

Diatonic major intervals used to denote Chord Additions

Constructors

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

type ChordLabel = Chord RootSource

A chord based on absolute Root notes

type ChordDegree = Chord ScaleDegreeSource

A chord based on relative ScaleDegrees

noneLabel :: ChordLabelSource

No Chord label

unknownLabel :: ChordLabelSource

Unknown Chord label

Derived types for classification of chords

data ClassType Source

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

data Triad Source

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

Tests

isNone :: Root -> BoolSource

Returns True if the Root is N, and False otherwise

isNoneChord :: ChordLabel -> BoolSource

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

isUnknown :: Root -> BoolSource

Returns True if the Root is unknown, and False otherwise

isRoot :: Root -> BoolSource

Returns True if the Root is not unknown or none

isAddition :: Addition -> BoolSource

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

Transformation and analysis of chords

toClassType :: Chord a -> ClassTypeSource

Returns the ClassType given a Chord. This function uses analyseDegClassType to analyse a chord and derive the ClassType

toTriad :: Chord a -> TriadSource

Takes a Chord and determines the Triad

>>> toTriad (Chord (Note Nothing C) Min [NoAdd (Note (Just Fl) I3),Add (Note Nothing I3)] 0 0)
maj 
>>> toTriad (Chord (Note Nothing C) HDim7 [Add (Note (Just Sh) I11)] 0 0)
dim
>>> toTriad (Chord (Note Nothing C) Min [NoAdd (Note (Just Fl) I3)] 0 0)
NoTriad

analyseDegTriad :: [Addition] -> TriadSource

Analyses a degree list and returns MajTriad, MinTriad or NoTriad if the degrees make a chord a major, minor, or no triad, respectivly.

toDegreeList :: Chord a -> [Addition]Source

Transforms a Chord into a list of relative degrees (i.e. Additions, without the root note).

>>> toDegreeList (Chord (Note Nothing C) HDim7 [Add (Note (Just Sh) I11)] 0 0)
[3b,5b,7b,11#]
>>> toDegreeList (Chord (Note Nothing C) Min13 [NoAdd (Note Nothing I11)] 0 0)
[3b,5,7b,9,13]
>>> toDegreeList (parseData pChord "D:7(b9)")
[3,5,7b,9b]

toMode :: Triad -> ModeSource

Converts a Shorthand to a Mode

simplifyRoot :: Root -> RootSource

Simplify note roots to a single enharmonic representation. For instance, D♭ becomes C♯, E♯ becomes F, and G𝄫 becomes F.

Scale degree transposition

toChordDegree :: Key -> ChordLabel -> ChordDegreeSource

Given a Key, calculates the the ChordDegree (i.e. relative, ScaleDegree based Chord) for an absolute ChordLabel using toScaleDegree.

toScaleDegree :: Key -> Root -> ScaleDegreeSource

Transformes a absolute Root Note into a relative ScaleDegree, given a Key.

transposeSem :: ScaleDegree -> Int -> ScaleDegreeSource

Transposes a scale degree with sem semitones up

toSemitone :: (Show a, Enum a) => Note a -> IntSource

Returns the semitone value [0 .. 11] of a ScaleDegree where 0 = C, e.g. F# = 6. For the constructors N and X an error is thrown.

toRoot :: Int -> RootSource

The reverse of toSemitone returning the 'Note DiatonicNatural' given a Integer [0..11] semitone, where 0 represents C. When the integer is out of the range [0..11] an error is thrown.