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

Copyright(c) Hans Hoglund 2012
LicenseBSD-style
Maintainerhans@hanshoglund.se
Stabilityexperimental
Portabilitynon-portable (TF,GNTD)
Safe HaskellNone
LanguageHaskell2010

Music.Pitch.Common.Interval

Contents

Description

Provides standard intervals.

Synopsis

Quality

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

Invert a quality.

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

isPerfect :: HasQuality a => a -> Bool Source

Returns whether the given quality is perfect.

isMajor :: HasQuality a => a -> Bool Source

Returns whether the given quality is major.

isMinor :: HasQuality a => a -> Bool Source

Returns whether the given quality is minor.

isAugmented :: HasQuality a => a -> Bool Source

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

isDiminished :: HasQuality a => a -> Bool Source

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

Number

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

Methods

number :: a -> Number Source

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 :: Number Source

A synonym for 1.

prime :: Number Source

A synonym for 2.

second :: Number Source

A synonym for 3.

third :: Number Source

A synonym for 4.

fourth :: Number Source

A synonym for 5.

fifth :: Number Source

A synonym for 6.

sixth :: Number Source

A synonym for 7.

seventh :: Number Source

A synonym for 8.

octave :: Number Source

A synonym for 9.

ninth :: Number Source

A synonym for 10.

tenth :: Number Source

A synonym for 11.

twelfth :: Number Source

A synonym for 13.

duodecim :: Number Source

A synonym for 14.

thirteenth :: Number Source

A synonym for 15.

fourteenth :: Number Source

A synonym for 16.

fifteenth :: Number Source

A synonym for 17.

Intervals

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

mkInterval :: Quality -> Number -> Interval Source

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

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

major :: Number -> Interval Source

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

minor :: Number -> Interval Source

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

augmented :: Number -> Interval Source

Creates an augmented interval.

diminished :: Number -> Interval Source

Creates a diminished interval.

doublyAugmented :: Number -> Interval Source

Creates a doubly augmented interval.

doublyDiminished :: Number -> Interval Source

Creates a doubly diminished interval.

Inspecting intervals

octaves :: Interval -> Octaves Source

Returns the non-simple part of an interval.

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

isNegative :: Interval -> Bool Source

Returns whether the given interval is negative.

isPositive :: Interval -> Bool Source

Returns whether the given interval is positive.

isNonNegative :: Interval -> Bool Source

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

isPerfectUnison :: Interval -> Bool Source

Returns whether the given interval a perfect unison.

isStep :: Interval -> Bool Source

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

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

Returns whether the given interval is simple.

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

isCompound :: Interval -> Bool Source

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

Returns the simple part of an interval.

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

Inversion

invert :: Interval -> Interval Source

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.

Utility

asInterval :: Interval -> Interval Source

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

intervalDiff :: Interval -> Int Source

Deprecated: This should be hidden

mkInterval' :: Int -> Int -> Interval Source

Deprecated: This should be hidden