mezzo-0.3.0.0: Typesafe music composition

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

Mezzo.Model.Harmony.Chords

Contents

Description

Types and type functions modelling harmonic chords.

Synopsis

Chords

data DyadType Source #

The type of a dyad.

Instances

Primitive DyadType MinThird Source # 

Associated Types

type Rep MinThird (a :: MinThird) :: * Source #

Methods

prim :: sing a -> Rep MinThird a Source #

pretty :: sing a -> String Source #

Primitive DyadType MajThird Source # 

Associated Types

type Rep MajThird (a :: MajThird) :: * Source #

Methods

prim :: sing a -> Rep MajThird a Source #

pretty :: sing a -> String Source #

Primitive DyadType PerfFourth Source # 

Associated Types

type Rep PerfFourth (a :: PerfFourth) :: * Source #

Methods

prim :: sing a -> Rep PerfFourth a Source #

pretty :: sing a -> String Source #

Primitive DyadType PerfFifth Source # 

Associated Types

type Rep PerfFifth (a :: PerfFifth) :: * Source #

Methods

prim :: sing a -> Rep PerfFifth a Source #

pretty :: sing a -> String Source #

Primitive DyadType PerfOct Source # 

Associated Types

type Rep PerfOct (a :: PerfOct) :: * Source #

Methods

prim :: sing a -> Rep PerfOct a Source #

pretty :: sing a -> String Source #

type Rep DyadType MinThird Source # 
type Rep DyadType MajThird Source # 
type Rep DyadType PerfFourth Source # 
type Rep DyadType PerfFifth Source # 
type Rep DyadType PerfOct Source # 
type Rep DyadType PerfOct = Int -> [Int]

data TriadType Source #

The type of a triad.

Instances

Primitive TriadType MajTriad Source # 

Associated Types

type Rep MajTriad (a :: MajTriad) :: * Source #

Methods

prim :: sing a -> Rep MajTriad a Source #

pretty :: sing a -> String Source #

Primitive TriadType MinTriad Source # 

Associated Types

type Rep MinTriad (a :: MinTriad) :: * Source #

Methods

prim :: sing a -> Rep MinTriad a Source #

pretty :: sing a -> String Source #

Primitive TriadType AugTriad Source # 

Associated Types

type Rep AugTriad (a :: AugTriad) :: * Source #

Methods

prim :: sing a -> Rep AugTriad a Source #

pretty :: sing a -> String Source #

Primitive TriadType DimTriad Source # 

Associated Types

type Rep DimTriad (a :: DimTriad) :: * Source #

Methods

prim :: sing a -> Rep DimTriad a Source #

pretty :: sing a -> String Source #

FunRep DyadType Int [Int] c => Primitive TriadType (DoubledD c) Source # 

Associated Types

type Rep (DoubledD c) (a :: DoubledD c) :: * Source #

Methods

prim :: sing a -> Rep (DoubledD c) a Source #

pretty :: sing a -> String Source #

type Rep TriadType MajTriad Source # 
type Rep TriadType MinTriad Source # 
type Rep TriadType AugTriad Source # 
type Rep TriadType DimTriad Source # 
type Rep TriadType (DoubledD c) Source # 
type Rep TriadType (DoubledD c) = Int -> [Int]

data TetradType Source #

The type of a tetrad.

Instances

Primitive TetradType MajSeventh Source # 

Associated Types

type Rep MajSeventh (a :: MajSeventh) :: * Source #

Methods

prim :: sing a -> Rep MajSeventh a Source #

pretty :: sing a -> String Source #

Primitive TetradType MajMinSeventh Source # 

Associated Types

type Rep MajMinSeventh (a :: MajMinSeventh) :: * Source #

Methods

prim :: sing a -> Rep MajMinSeventh a Source #

pretty :: sing a -> String Source #

Primitive TetradType MinSeventh Source # 

Associated Types

type Rep MinSeventh (a :: MinSeventh) :: * Source #

Methods

prim :: sing a -> Rep MinSeventh a Source #

pretty :: sing a -> String Source #

Primitive TetradType HalfDimSeventh Source # 

Associated Types

type Rep HalfDimSeventh (a :: HalfDimSeventh) :: * Source #

Methods

prim :: sing a -> Rep HalfDimSeventh a Source #

pretty :: sing a -> String Source #

Primitive TetradType DimSeventh Source # 

Associated Types

type Rep DimSeventh (a :: DimSeventh) :: * Source #

Methods

prim :: sing a -> Rep DimSeventh a Source #

pretty :: sing a -> String Source #

FunRep TriadType Int [Int] c => Primitive TetradType (DoubledT c) Source # 

Associated Types

type Rep (DoubledT c) (a :: DoubledT c) :: * Source #

Methods

prim :: sing a -> Rep (DoubledT c) a Source #

pretty :: sing a -> String Source #

type Rep TetradType MajSeventh Source # 
type Rep TetradType MajMinSeventh Source # 
type Rep TetradType MinSeventh Source # 
type Rep TetradType HalfDimSeventh Source # 
type Rep TetradType DimSeventh Source # 
type Rep TetradType (DoubledT c) Source # 
type Rep TetradType (DoubledT c) = Int -> [Int]

data Inversion Source #

The inversion of a chord.

Constructors

Inv0 
Inv1 
Inv2 
Inv3 

Instances

Primitive Inversion Inv0 Source # 

Associated Types

type Rep Inv0 (a :: Inv0) :: * Source #

Methods

prim :: sing a -> Rep Inv0 a Source #

pretty :: sing a -> String Source #

Primitive Inversion Inv1 Source # 

Associated Types

type Rep Inv1 (a :: Inv1) :: * Source #

Methods

prim :: sing a -> Rep Inv1 a Source #

pretty :: sing a -> String Source #

Primitive Inversion Inv2 Source # 

Associated Types

type Rep Inv2 (a :: Inv2) :: * Source #

Methods

prim :: sing a -> Rep Inv2 a Source #

pretty :: sing a -> String Source #

Primitive Inversion Inv3 Source # 

Associated Types

type Rep Inv3 (a :: Inv3) :: * Source #

Methods

prim :: sing a -> Rep Inv3 a Source #

pretty :: sing a -> String Source #

type Rep Inversion Inv0 Source # 
type Rep Inversion Inv0 = [Int] -> [Int]
type Rep Inversion Inv1 Source # 
type Rep Inversion Inv1 = [Int] -> [Int]
type Rep Inversion Inv2 Source # 
type Rep Inversion Inv2 = [Int] -> [Int]
type Rep Inversion Inv3 Source # 
type Rep Inversion Inv3 = [Int] -> [Int]

data DyaType t Source #

The singleton type for DyadType

Constructors

DyaType 

data TriType t Source #

The singleton type for TriadType.

Constructors

TriType 

data TetType t Source #

The singleton type for TetradType.

Constructors

TetType 

data Inv t Source #

The singleton type for Inversion.

Constructors

Inv 

type family InvertChord (c :: ChordType n) :: ChordType n where ... Source #

Invert a chord once.

Equations

InvertChord (Dyad r t Inv0) = Dyad r t Inv1 
InvertChord (Dyad r t Inv1) = Dyad r t Inv0 
InvertChord (Triad r t Inv2) = Triad r t Inv0 
InvertChord (Triad r t i) = Triad r t (InvSucc i) 
InvertChord (Tetrad r t i) = Tetrad r t (InvSucc i) 

data ChordType :: Nat -> Type where Source #

A chord type, indexed by the number of notes.

Constructors

Dyad :: RootType -> DyadType -> Inversion -> ChordType 2

A dyad, consisting of two pitches.

Triad :: RootType -> TriadType -> Inversion -> ChordType 3

A triad, consisting of three pitches.

Tetrad :: RootType -> TetradType -> Inversion -> ChordType 4

A tetrad, consisting of four pitches.

Instances

(IntRep RootType r, FunRep DyadType Int [Int] t, FunRep Inversion [Int] [Int] i) => Primitive (ChordType 2) (Dyad r t i) Source # 

Associated Types

type Rep (Dyad r t i) (a :: Dyad r t i) :: * Source #

Methods

prim :: sing a -> Rep (Dyad r t i) a Source #

pretty :: sing a -> String Source #

(IntRep RootType r, FunRep TriadType Int [Int] t, FunRep Inversion [Int] [Int] i) => Primitive (ChordType 3) (Triad r t i) Source # 

Associated Types

type Rep (Triad r t i) (a :: Triad r t i) :: * Source #

Methods

prim :: sing a -> Rep (Triad r t i) a Source #

pretty :: sing a -> String Source #

(IntRep RootType r, FunRep DyadType Int [Int] dt, FunRep Inversion [Int] [Int] i) => Primitive (ChordType 3) (Triad r (DoubledD dt) i) Source # 

Associated Types

type Rep (Triad r (DoubledD dt) i) (a :: Triad r (DoubledD dt) i) :: * Source #

Methods

prim :: sing a -> Rep (Triad r (DoubledD dt) i) a Source #

pretty :: sing a -> String Source #

(IntRep RootType r, FunRep TetradType Int [Int] t, FunRep Inversion [Int] [Int] i) => Primitive (ChordType 4) (Tetrad r t i) Source # 

Associated Types

type Rep (Tetrad r t i) (a :: Tetrad r t i) :: * Source #

Methods

prim :: sing a -> Rep (Tetrad r t i) a Source #

pretty :: sing a -> String Source #

(IntRep RootType r, FunRep TriadType Int [Int] tt, FunRep Inversion [Int] [Int] i) => Primitive (ChordType 4) (Tetrad r (DoubledT tt) i) Source # 

Associated Types

type Rep (Tetrad r (DoubledT tt) i) (a :: Tetrad r (DoubledT tt) i) :: * Source #

Methods

prim :: sing a -> Rep (Tetrad r (DoubledT tt) i) a Source #

pretty :: sing a -> String Source #

type Rep (ChordType 2) (Dyad r t i) Source # 
type Rep (ChordType 2) (Dyad r t i) = [Int]
type Rep (ChordType 3) (Triad r t i) Source # 
type Rep (ChordType 3) (Triad r t i) = [Int]
type Rep (ChordType 3) (Triad r (DoubledD dt) i) Source # 
type Rep (ChordType 3) (Triad r (DoubledD dt) i) = [Int]
type Rep (ChordType 4) (Tetrad r t i) Source # 
type Rep (ChordType 4) (Tetrad r t i) = [Int]
type Rep (ChordType 4) (Tetrad r (DoubledT tt) i) Source # 
type Rep (ChordType 4) (Tetrad r (DoubledT tt) i) = [Int]

data Cho c Source #

The singleton type for ChordType.

Constructors

Cho 

type family FromChord (c :: ChordType n) (l :: Nat) :: Partiture n l where ... Source #

Convert a chord to a partiture with the given length (one voice for each pitch).

Equations

FromChord c l = VectorToColMatrix (ChordToPitchList c) l