acts-0.2.0.0: Semigroup actions, groups, and torsors.
Safe HaskellNone
LanguageHaskell2010

Acts.Examples.MusicalIntervals

Description

Illustrative usage of Group, Act and Torsor: manipulation of musical intervals.

The musical distance between two musical notes is a musical interval.

Intervals can be compounded and inverted, so they form a Group.

Notes can be translated by a given interval, which is an Act of intervals on notes.

There's a unique musical interval taking any note to any other given one, so notes are a torsor under intervals.

This functionality is useful in providing enharmonically correct voicings of chords.

Synopsis

Musical notes

We begin by defining note names, which are acted upon by the cyclic group of order 7.

type C7 = Sum (Finite 7) Source #

Cyclic group of order 7.

data NoteName Source #

Musical note names.

The enumeration starts with C to conform with scientific pitch notation.

Constructors

C 
D 
E 
F 
G 
A 
B 

Instances

Instances details
Bounded NoteName Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Enum NoteName Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Eq NoteName Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Ord NoteName Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Show NoteName Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Generic NoteName Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Associated Types

type Rep NoteName :: Type -> Type #

Methods

from :: NoteName -> Rep NoteName x #

to :: Rep NoteName x -> NoteName #

Finitary NoteName Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Associated Types

type Cardinality NoteName :: Nat #

Act C7 NoteName Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Methods

(•) :: C7 -> NoteName -> NoteName

act :: C7 -> NoteName -> NoteName

Torsor C7 NoteName Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Methods

(<--) :: NoteName -> NoteName -> C7

(-->) :: NoteName -> NoteName -> C7

type Rep NoteName Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

type Rep NoteName = D1 ('MetaData "NoteName" "Acts.Examples.MusicalIntervals" "acts-0.2.0.0-inplace-acts-examples" 'False) ((C1 ('MetaCons "C" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "D" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "E" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "F" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "G" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "A" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "B" 'PrefixI 'False) (U1 :: Type -> Type))))
type Cardinality NoteName Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

type Cardinality NoteName = GCardinality (Rep NoteName)

In this case we used DerivingVia to derive the action of C7 through the Finitary instance of NoteName by using the Finitely newtype.

newtype Alteration Source #

Alterations, i.e. sharps and flats.

Pattern synonyms such as Sharp and Flat are also bundled.

Constructors

Alteration 

Fields

Note the use of DerivingVia to transfer algebraic operations from Sum Int.

For non-newtypes, one can use generics, for example:

data Klein4 = Klein4 ( C 2 ) ( C 2 )
  deriving stock Generic
  deriving ( Semigroup, Monoid, Group )
    via Generically Klein4

This uses the Generically newtype from the generic-data library.

data Note Source #

Note names such as A4 or C#6: note name, alteration, and octave (scientific pitch notation).

Constructors

Note 

Instances

Instances details
Show Note Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Methods

showsPrec :: Int -> Note -> ShowS #

show :: Note -> String #

showList :: [Note] -> ShowS #

Act Interval Note Source #

Intervallically correct action of intervals on notes.

  • minor third up from C: Eb
  • minor third up from A: C.
Instance details

Defined in Acts.Examples.MusicalIntervals

Methods

(•) :: Interval -> Note -> Note

act :: Interval -> Note -> Note

Torsor Interval Note Source #

Computes the interval between two notes.

> Note C Natural 5 --> Note A Natural 4
minor 3rd down
> Note E Flat 4 --> Note A Natural 5
augmented 11th up
Instance details

Defined in Acts.Examples.MusicalIntervals

Methods

(<--) :: Note -> Note -> Interval

(-->) :: Note -> Note -> Interval

Musical intervals

An interval is represented as a number of scale steps to take (relative to the major scale), together with an additional alteration to apply.

For instance, a major third is two steps up (diatonic steps relative to the root in a major scale):

> Steps ( Sum 2 ) Natural
major 3rd up

A minor sixth is 5 steps up, and then a flat:

> Steps ( Sum 5 ) Flat
minor 6th up

The smart constructor Interval is also provided that is more intuitive to use:

> Interval 3 Natural
major 3rd up
> Interval 7 Flat
minor 7th up

Note that the Semigroup/Group operations on intervals are not the obvious ones, e.g.:

> Steps ( Sum 2 ) Natural
major 3rd up
> Steps ( Sum (-2) ) Natural
minor 3rd down
> inverse ( Steps ( Sum 2 ) Natural )
Steps ( Sum (-2) ) Flat
major 3rd down

data Interval Source #

Musical interval: steps (relative to the root in a major scale) and additional alteration.

Instances

Instances details
Show Interval Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Semigroup Interval Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Monoid Interval Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Group Interval Source # 
Instance details

Defined in Acts.Examples.MusicalIntervals

Act Interval Note Source #

Intervallically correct action of intervals on notes.

  • minor third up from C: Eb
  • minor third up from A: C.
Instance details

Defined in Acts.Examples.MusicalIntervals

Methods

(•) :: Interval -> Note -> Note

act :: Interval -> Note -> Note

Torsor Interval Note Source #

Computes the interval between two notes.

> Note C Natural 5 --> Note A Natural 4
minor 3rd down
> Note E Flat 4 --> Note A Natural 5
augmented 11th up
Instance details

Defined in Acts.Examples.MusicalIntervals

Methods

(<--) :: Note -> Note -> Interval

(-->) :: Note -> Note -> Interval

semitones :: Interval -> Int Source #

Compute the number of semitones in an interval, using the reference of the C major scale.

To define algebraic operations on intervals, we use an equivariant bijection to the product group ( Sum Int, Sum Int ).

Note that ( Sum Int, Sum Int ) is automatically a Semigroup, Monoid and Group using the product structure.

straighten :: Interval -> (Sum Int, Sum Int) Source #

Forward part of the bijection.

twist :: (Sum Int, Sum Int) -> Interval Source #

Back part of the bijection.

Illustration of the functionality

Chords

majorTriad :: [Interval] Source #

Major triad: major third, perfect fifth.

diminished7th :: [Interval] Source #

Diminished seventh chord: minor third, diminished fifth, diminished seventh.

minor11th :: [Interval] Source #

Minor 11th chord (Kenny Barron voicing).

Example chords:

> majorTriad <&> ( • Note C Natural 4 )
[C4,E4,G4]
> diminished7th <&> ( • Note G Sharp 3 )
[G#3,B3,D4,F4]
> minor11th <&> ( • Note D Natural 3 )
[D3,A3,E4,F4,C5,G5]

Scales

mode :: NoteName -> [Interval] Source #

Modes of C major.

phrygian :: [Interval] Source #

Phrygian scale.

lydian :: [Interval] Source #

Lydian scale.

wholeTone :: [Interval] Source #

Whole tone scale.

Example scales:

> phrygian <&> ( • Note E Natural 3 )
[E3,F3,G3,A3,B3,C4,D4,E4]
> phrygian <&> ( • Note C Sharp 3 )
[C#3,D3,E3,F#3,G#3,A3,B3,C#4]
> lydian <&> ( • Note C Natural 4 )
[C4,D4,E4,F#4,G4,A4,B4,C5]
> wholeTone <&> ( • Note G Natural 5 )
[G5,A5,B5,C#6,Eb6,F6]

Helper code

End of main example code.

Follows: helper code for reading/showing musical notes and intervals.

pattern Flat :: Alteration Source #