mezzo-0.3.1.0: Typesafe music composition

Copyright(c) Dima Szamozvancev
LicenseMIT
Maintainerds709@cam.ac.uk
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Mezzo.Compose.Harmony

Contents

Description

Literals for chords and progressions.

Synopsis

Functional harmony terms

type InKey k v = KeyS k -> v Source #

Type of harmonic terms in some key.

Progressions

prog :: ValidProg r t p => InKey k (PhraseList p) -> Music (Sig :: Signature t k r) (FromProg p t) Source #

Create a new musical progression from the given time signature and progression schema.

Phrases

data PhraseList p where Source #

List of phrases in a progression parameterised by the key, ending with a cadence.

Constructors

Cdza :: Cad c -> KeyS k -> PhraseList (CadPhrase c)

A cadential phrase, ending the progression.

(:+) :: InKey k (Phr p) -> InKey k (PhraseList ps) -> KeyS k -> PhraseList (p := ps) infixr 5

Add a new phrase to the beginning of the progression.

cadence :: InKey k (Cad c) -> InKey k (PhraseList (CadPhrase c)) Source #

Create a new cadential phrase.

ph_I :: InKey k (Ton (t :: Tonic k l)) -> InKey k (Phr (PhraseI t :: Phrase k l)) Source #

Dominant-tonic phrase.

ph_VI :: InKey k (Dom (d :: Dominant k l1)) -> InKey k (Ton (t :: Tonic k (l - l1))) -> InKey k (Phr (PhraseVI d t :: Phrase k l)) Source #

Dominant-tonic phrase.

ph_IVI :: InKey k (Ton (t1 :: Tonic k (l2 - l1))) -> InKey k (Dom (d :: Dominant k l1)) -> InKey k (Ton (t2 :: Tonic k (l - l2))) -> InKey k (Phr (PhraseIVI t1 d t2 :: Phrase k l)) Source #

Tonic-dominant-tonic phrase.

Cadences

auth_V_I :: InKey k (Cad (AuthCad (DegChord :: DegreeC V MajQ k Inv1 Oct2) (DegChord :: DegreeC I (KeyToQual k) k Inv0 Oct3))) Source #

Authentic V-I dominant cadence.

auth_V7_I :: InKey k (Cad (AuthCad7 (DegChord :: DegreeC V DomQ k Inv2 Oct2) (DegChord :: DegreeC I (KeyToQual k) k Inv0 Oct3))) Source #

Authentic V7-I dominant seventh cadence.

auth_vii_I :: InKey k (Cad (AuthCadVii (DegChord :: DegreeC VII DimQ k Inv1 Oct2) (DegChord :: DegreeC I (KeyToQual k) k Inv0 Oct3))) Source #

Authentic vii-I leading tone cadence.

auth_64_V7_I :: InKey k (Cad (AuthCad64 (DegChord :: DegreeC I (KeyToQual k) k Inv2 Oct3) (DegChord :: DegreeC V DomQ k Inv3 Oct2) (DegChord :: DegreeC I (KeyToQual k) k Inv1 Oct3))) Source #

Authentic cadential 6-4 cadence.

full :: InKey k (Sub s) -> InKey k (Cad c) -> InKey k (Cad (FullCad s c)) Source #

Full cadence, starting with a subdominant.

end :: InKey k (PhraseList (CadPhrase NoCad)) Source #

End progression without an explicit cadence.

Tonic chords

ton :: InKey k (Ton (TonT (DegChord :: DegreeC I (KeyToQual k) k Inv0 Oct3))) Source #

Tonic chord.

ton_T_T :: InKey k (Ton ton1) -> InKey k (Ton ton2) -> InKey k (Ton (TonTT ton1 ton2)) Source #

Doubled tonics.

Dominants

dom_V :: InKey k (Dom (DomVM (DegChord :: DegreeC V MajQ k Inv2 Oct2))) Source #

Dominant (V) chord.

dom_V7 :: InKey k (Dom (DomV7 (DegChord :: DegreeC V DomQ k Inv2 Oct2))) Source #

Dominant seventh (V7) chord.

dom_vii0 :: InKey k (Dom (DomVii0 (DegChord :: DegreeC VII DimQ k Inv1 Oct2))) Source #

Dominant leading tone (vii) chord.

dom_II_V7 :: InKey k (Dom (DomSecD (DegChord :: DegreeC II DomQ k Inv0 Oct3) (DegChord :: DegreeC V DomQ k Inv2 Oct2))) Source #

Secondary dominant - dominant (V/V-V7) chord.

dom_S_D :: InKey k (Sub subdom) -> InKey k (Dom dom) -> InKey k (Dom (DomSD subdom dom)) Source #

Subdominant followed by a dominant.

dom_D_D :: InKey k (Dom dom1) -> InKey k (Dom dom2) -> InKey k (Dom (DomDD dom1 dom2)) Source #

Dominant followed by another dominant.

Subdominants

subdom_IV :: InKey k (Sub (SubIV (DegChord :: DegreeC IV (KeyToQual k) k Inv2 Oct2))) Source #

Subdominant fourth (IV) chord.

subdom_ii :: IsMajor k "ii subdominant" => InKey k (Sub (SubIIm (DegChord :: DegreeC II MinQ k Inv0 Oct3))) Source #

Subdominant minor second (ii) chord.

subdom_iii_IV :: IsMajor k "iii-IV subdominant" => InKey k (Sub (SubIIImIVM (DegChord :: DegreeC III MinQ k Inv0 Oct3) (DegChord :: DegreeC IV MajQ k Inv3 Oct2))) Source #

Subdominant third-fourth (iii-IV) progression.

subdom_S_S :: InKey k (Sub sub1) -> InKey k (Sub sub2) -> InKey k (Sub (SubSS sub1 sub2)) Source #

Doubled subdominants.

Time signatures

duple :: TimeSig 2 Source #

Duple meter (2/4).

triple :: TimeSig 3 Source #

Triple meter (3/4).

quadruple :: TimeSig 4 Source #

Quadruple meter (4/4).

Key literals