music-pitch-1.6: Abstract representation of musical pitch.

Portabilitynon-portable (TF,GNTD)
Stabilityexperimental
Maintainerhans@hanshoglund.se
Safe HaskellNone

Music.Pitch.Common

Contents

Description

Provides a representation of pitch as defined in Common Music Theory (CMT).

Synopsis

Enharmonic representation

Octaves

data Octaves Source

An interval represented as a number of octaves, including negative intervals.

 octaves a = semitones a `div` 12
 steps   a = semitones a `mod` 12

class HasOctaves a whereSource

Class of intervals that has a number of Octaves.

Methods

octaves :: a -> OctavesSource

Returns the number of octaves spanned by an interval.

The number of octaves is negative if and only if the interval is negative.

Examples:

 octaves (perfect unison)  =  0
 octaves (d5 ^* 4)         =  2
 octaves (-_P8)            =  -1

Steps

data Steps Source

An interval represented as a number of steps in the range 0 ≤ x < 12.

 octaves a = semitones a `div` 12
 steps   a = semitones a `mod` 12

class HasSteps a whereSource

Class of intervals that has a number of Steps.

Methods

steps :: a -> StepsSource

The number of steps is always in the range 0 ≤ x < 12.

Examples:

 octaves (perfect unison)  =  0
 octaves (d5 ^* 4)         =  2
 octaves (-m7)             =  -1

Semitones

data Semitones Source

An interval represented as a number of semitones, including negative intervals, as well as intervals larger than one octave. This representation does not take spelling into account, so for example a major third and a diminished fourth can not be distinguished.

Intervals that name a number of semitones (i.e. semitone, tritone) does not have an unequivocal spelling. To convert these to an interval, a Spelling must be provided as in:

 spell sharps tritone == augmented fourth
 spell flats  tritone == diminished fifth

class HasSemitones a whereSource

Class of intervals that can be converted to a number of Semitones.

Methods

semitones :: a -> SemitonesSource

Returns the number of semitones spanned by an interval.

The number of semitones is negative if and only if the interval is negative.

Examples:

 semitones (perfect unison)  =  0
 semitones tritone           =  6
 semitones d5                =  6
 semitones (-_P8)            =  -12

semitone :: SemitonesSource

Precisely one semitone.

tone :: SemitonesSource

Precisely one whole tone, or two semitones.

ditone :: SemitonesSource

Precisely two whole tones, or four semitones.

tritone :: SemitonesSource

Precisely three whole tones, or six semitones.

isSemitone :: HasSemitones a => a -> BoolSource

Returns true iff the given interval spans one semitone.

isTone :: HasSemitones a => a -> BoolSource

Returns true iff the given interval spans one whole tone (two semitones).

isTritone :: HasSemitones a => a -> BoolSource

Returns true iff the given interval spans three whole tones (six semitones).

Enharmonic equivalence

(=:=) :: HasSemitones a => a -> a -> BoolSource

Enharmonic equivalence.

(/:=) :: HasSemitones a => a -> a -> BoolSource

Enharmonic non-equivalence.

Pitches

Name type

data Name Source

A pitch name.

Constructors

C 
D 
E 
F 
G 
A 
B 

Instances

Accidental type

data Accidental Source

An accidental is either flat, natural or sharp.

This representation allows for an arbitrary number of flats or sharps rather than just single (the ♯ and ♭ symbols) and double (i.e. the x and ♭♭ symbols).

The Num and Enum instances treat Accidental as the number of altered semitones, i.e. a double flat is -2, natural 0 and so on.

Instances

Enum Accidental 
Eq Accidental 
Integral Accidental 
Num Accidental 
Ord Accidental 
Real Accidental 
Show Accidental 
Alterable Accidental 
(IsPitch a, Alterable a) => IsPitch (Accidental -> a)

  Magic instance that allow us to write c sharp instead of sharpen c. Requires FlexibleInstances.

doubleFlat :: AccidentalSource

The double flat accidental.

flat :: AccidentalSource

The flat accidental.

natural :: AccidentalSource

The natural accidental.

sharp :: AccidentalSource

The sharp accidental.

doubleSharp :: AccidentalSource

The double sharp accidental.

Inspecting accidentals

isNatural :: Accidental -> BoolSource

 Returns whether this is a natural accidental.

isSharpened :: Accidental -> BoolSource

 Returns whether this is a sharp, double sharp etc.

isFlattened :: Accidental -> BoolSource

 Returns whether this is a flat, double flat etc.

isStandard :: Accidental -> BoolSource

 Returns whether this is a standard accidental, i.e. either a double flat, flat, natural, sharp or doubl sharp.

Pitch type

data Pitch Source

Common pitch representation.

Intervals and pitches can be added using .+^. To get the interval between two pitches, use .-..

Pitches are normally entered using the following literals.

 c d e f g a b

Notes with accidentals can be written by adding the s or b suffices (or two for double sharps and flats).

 cs, ds, es ...    -- sharp
 cb, db, eb ...    -- flat
 css, dss, ess ... -- double sharp
 cbb, dbb, ebb ... -- double flat

There is also a convenience syntax for entering pitches one octave up or down, using ' and _ respectively.

 g a b c'
 d c b_ c

Because of some overloading magic, we can actually write sharp and flat as postfix functions. This gives a better read:

 cs == c sharp
 db == c flat

You can of course use typical functional transformation of pitch as well. For example sharpen and flatten are the ordinary (prefix) versions of sharp and flat

 sharpen c             == c sharp       == cs
 flatten d             == d flat        == ds
 (sharpen . sharpen) c == c doubleSharp == css
 (flatten . flatten) d == d doubleFlat  == dss

Note that there is no guarantee that your pitch representation use enharmonic equivalence, so cs == db may or may not hold.

 c .+^ minor third == eb
 f .-. c           == perfect fourth

Pitches are described by name, accidental and octave number.

 c   == fromIntegral 0
 _P4 == perfect fourth   == interval Perfect 5
 d5  == diminished fifth == diminish (perfect fifth)

pitch :: Name -> Accidental -> PitchSource

Creates a pitch from name accidental.

name :: Pitch -> NameSource

Returns the name of a pitch.

To convert a pitch to a numeric type, use octaves, steps or semitones on the relevant interval type, for example:

 semitones (a' .-. middleC)

accidental :: Pitch -> AccidentalSource

Returns the accidental of a pitch.

See also octaves, and steps and semitones.

asPitch :: Pitch -> PitchSource

This is just the identity function, but is useful to fix the type of Pitch.

Intervals

Number type

data Number Source

The number portion of an interval (i.e. second, third, etc).

Note that the interval number is always one step larger than number of steps spanned by the interval (i.e. a third spans two diatonic steps). Thus number does not distribute over addition:

 number (a + b) = number a + number b - 1

class HasNumber a whereSource

Methods

number :: a -> NumberSource

Returns the number portion of an interval.

The interval number is negative if and only if the interval is negative.

See also quality, octaves and semitones.

unison :: NumberSource

A synonym for 1.

prime :: NumberSource

A synonym for 2.

second :: NumberSource

A synonym for 3.

third :: NumberSource

A synonym for 4.

fourth :: NumberSource

A synonym for 5.

fifth :: NumberSource

A synonym for 6.

sixth :: NumberSource

A synonym for 7.

seventh :: NumberSource

A synonym for 8.

octave :: NumberSource

A synonym for 9.

ninth :: NumberSource

A synonym for 10.

tenth :: NumberSource

A synonym for 11.

twelfth :: NumberSource

A synonym for 13.

duodecim :: NumberSource

A synonym for 14.

thirteenth :: NumberSource

A synonym for 15.

fourteenth :: NumberSource

A synonym for 16.

fifteenth :: NumberSource

A synonym for 17.

Quality type

data Quality Source

Interval quality is either perfect, major, minor, augmented, and diminished. This representation allows for an arbitrary number of augmentation or diminishions, so augmented is represented by Augmented 1, doubly augmented by Augmented 2 and so on.

The quality of a compound interval is the quality of the simple interval on which it is based.

invertQuality :: Quality -> QualitySource

Invert a quality.

Perfect is unaffected, major becomes minor and vice versa, augmented becomes diminished and vice versa.

isPerfect :: HasQuality a => a -> BoolSource

Returns whether the given quality is perfect.

isMajor :: HasQuality a => a -> BoolSource

Returns whether the given quality is major.

isMinor :: HasQuality a => a -> BoolSource

Returns whether the given quality is minor.

isAugmented :: HasQuality a => a -> BoolSource

Returns whether the given quality is augmented (including double augmented etc).

isDiminished :: HasQuality a => a -> BoolSource

Returns whether the given quality is diminished (including double diminished etc).

Interval type

data Interval Source

An interval is the difference between two pitches, incuding negative intervals.

Intervals and pitches can be added using .+^. To get the interval between two pitches, use .-..

 c .+^ minor third == eb
 f .-. c           == perfect fourth

Adding intervals preserves spelling. For example:

 m3 ^+^ _M3 = _P5
 d5 ^+^ _M6 = m10

The scalar type of Interval is Integer, using ^* to stack intervals of a certain type on top of each other. For example _P5 ^* 2 is a stack of 2 perfect fifths, or a major ninth. The Num instance works as expected for +, negate and abs, and (arbitrarily) uses minor seconds for multiplication. If you find yourself *, or signum on intervals, consider switching to *^ or normalized.

Intervals are generally described in terms of Quality and Number. To construct an interval, use the interval constructor, the utility constructors major, minor, augmented and diminished, or the interval literals:

 m5  == minor   fifth    == interval Minor   5
 _P4 == perfect fourth   == interval Perfect 5
 d5  == diminished fifth == diminish (perfect fifth)

Creating intervals

interval :: Quality -> Number -> IntervalSource

Creates an interval from a quality and number.

Given Perfect with an number not indicating a perfect consonant, interval returns a major interval instead. Given Major or Minor with a number indicating a perfect consonance, interval returns a perfect or diminished interval respectively.

perfect :: Number -> IntervalSource

Creates a perfect interval. If given an inperfect number, constructs a major interval.

major :: Number -> IntervalSource

Creates a major interval. If given a perfect number, constructs a perfect interval.

minor :: Number -> IntervalSource

Creates a minor interval. If given a perfect number, constructs a diminished interval.

augmented :: Number -> IntervalSource

Creates an augmented interval.

diminished :: Number -> IntervalSource

Creates a diminished interval.

doublyAugmented :: Number -> IntervalSource

Creates a doubly augmented interval.

doublyDiminished :: Number -> IntervalSource

Creates a doubly diminished interval.

asInterval :: Interval -> IntervalSource

This is just the identity function, but is useful to fix the type of Interval.

Inspecting intervals

isNegative :: Interval -> BoolSource

Returns whether the given interval is negative.

isPositive :: Interval -> BoolSource

Returns whether the given interval is positive.

isNonNegative :: Interval -> BoolSource

Returns whether the given interval is non-negative. This implies that it is either positive or a perfect unison.

isPerfectUnison :: Interval -> BoolSource

Returns whether the given interval a perfect unison.

isStep :: Interval -> BoolSource

Returns whether the given interval is a step (a second or smaller).

Only diatonic number is taken into account, so _A2 is considered a step and m3 a leap, even though they have the same number of semitones.

isLeap :: Interval -> BoolSource

Returns whether the given interval is a leap (larger than a second).

Only the diatonic number is taken into account, so _A2 is considered a step and m3 a leap, even though they have the same number of semitones.

Simple and compound intervals

isSimple :: Interval -> BoolSource

Returns whether the given interval is simple.

A simple interval is a non-negative interval spanning less than one octave.

isCompound :: Interval -> BoolSource

Returns whether the given interval is compound.

A compound interval is either a negative interval, or a positive interval spanning more than octave.

separate :: Interval -> (Octaves, Interval)Source

Separate a compound interval into octaves and a simple interval.

 (perfect octave)^*x + y = z  iff  (x, y) = separate z

simple :: Interval -> IntervalSource

Returns the simple part of an interval.

 (perfect octave)^*x + y = z  iff  y = simple z

Inversion

invert :: Interval -> IntervalSource

Intervallic inversion.

The inversion an interval is determined as follows:

  • The number of a simple interval the difference of nine and the number of its inversion.
  • The quality of a simple interval is the inversion of the quality of its inversion.
  • The inversion of a compound interval is the inversion of its simple component.

Miscellaneous