HarmTrace-Base-1.5.3.1: 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.PitchClass

Contents

Description

Summary: this module provides some functions that transform notes and chords into pitch classes and pitch class sets. See for more info: http://en.wikipedia.org/wiki/Pitch_class

Synopsis

Documentation

data PCSet Source #

We hide the constructors, such that a PCSet can only be constructed with toPitchClasses, this to overcome confusion between interval sets and pitch class sets, which are both IntSets

Instances

Eq PCSet Source # 

Methods

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

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

Show PCSet Source # 

Methods

showsPrec :: Int -> PCSet -> ShowS #

show :: PCSet -> String #

showList :: [PCSet] -> ShowS #

Generic PCSet Source # 

Associated Types

type Rep PCSet :: * -> * #

Methods

from :: PCSet -> Rep PCSet x #

to :: Rep PCSet x -> PCSet #

Binary PCSet Source # 

Methods

put :: PCSet -> Put #

get :: Get PCSet #

putList :: [PCSet] -> Put #

type Rep PCSet Source # 
type Rep PCSet = D1 (MetaData "PCSet" "HarmTrace.Base.Chord.PitchClass" "HarmTrace-Base-1.5.3.1-3qA2fvFtftT46JVsdcg0NC" True) (C1 (MetaCons "PCSet" PrefixI True) (S1 (MetaSel (Just Symbol "pc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IntSet)))

Pitch classes

toPitchClass :: Diatonic a => Note a -> Int Source #

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.

pcToRoot :: Int -> Root Source #

The reverse of toPitchClass returning the 'Note DiatonicNatural' given a Integer [0..11] semitone, where 0 represents C. All pitch spelling is ignored and the the following twelve pitch names will be output: C, C#, D, Eb, E, F F#, G, Ab, A, Bb, B. When the integer is out of the range [0..11] an error is thrown.

Pitch classes applied to chords

toPitchClasses :: ChordLabel -> PCSet Source #

Similar to toIntSet but returns Int pitch classes and includes the Root and the bass Note of the the Chord. toPitchClasses throws an error when applied to a NoChord or UndefChord.

rootPC :: ChordLabel -> Int Source #

A short-cut applying toPitchClass to a Chord. rootPC throws an error when applied to a NoChord or UndefChord.

bassPC :: ChordLabel -> Int Source #

A short-cut applying intValToPitchClss to a Chord. bassPC throws an error when applied to a NoChord or UndefChord.

ignorePitchSpelling :: ChordLabel -> ChordLabel Source #

Ignores the pitch spelling of a chord by applying pcToRoot and toPitchClass to the root of a ChordLabel.

Pitch classes applied to keys

keyPitchClasses :: Key -> PCSet Source #

Return the set of pitches for the given key.

Pitch classes applied to interval sets

intValToPitchClss :: Root -> Interval -> Int Source #

As toIntervalClss, but returns the Int pitch class.

intSetToPC :: IntSet -> Root -> PCSet Source #

Transforms an interval set to and a root into a PCSet

Enharmonic Equivalence

class EnHarEq a where Source #

A class to compare datatypes that sound the same (they contain the same pitch class content): http://en.wikipedia.org/wiki/Enharmonic

Methods

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

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

Diatonic Class

class (Generic a, Show a, Enum a, Bounded a) => Diatonic a Source #

A class to mark certain datatypes to have a diatonic structure: http://en.wikipedia.org/wiki/Diatonic_and_chromatic