mezzo-0.2.0.2: 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 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 #

type Rep TriadType MajTriad Source # 
type Rep TriadType MinTriad Source # 
type Rep TriadType AugTriad Source # 
type Rep TriadType DimTriad Source # 

data SeventhType Source #

The type of a seventh chord.

Instances

Primitive SeventhType MajSeventh Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive SeventhType MajMinSeventh Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive SeventhType MinSeventh Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive SeventhType HalfDimSeventh Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive SeventhType 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 SeventhType (Doubled c) Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

type Rep SeventhType MajSeventh Source # 
type Rep SeventhType MajMinSeventh Source # 
type Rep SeventhType MinSeventh Source # 
type Rep SeventhType HalfDimSeventh Source # 
type Rep SeventhType DimSeventh Source # 
type Rep SeventhType (Doubled c) Source # 
type Rep SeventhType (Doubled 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 TriType t Source #

The singleton type for TriadType.

Constructors

TriType 

data SevType t Source #

The singleton type for SeventhType.

Constructors

SevType 

data Inv t Source #

The singleton type for Inversion.

Constructors

Inv 

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

Equations

InvertChord (Triad r t Inv2) = Triad r t Inv0 
InvertChord (Triad r t i) = Triad r t (InvSucc i) 
InvertChord (SeventhChord r t i) = SeventhChord r t (InvSucc i) 

data ChordType :: Nat -> Type where Source #

A chord type, indexed by the number of notes.

Instances

(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 SeventhType Int [Int] t, FunRep Inversion [Int] [Int] i) => Primitive (ChordType 4) (SeventhChord r t i) Source # 

Associated Types

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

Methods

prim :: sing a -> Rep (SeventhChord 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) (SeventhChord r (Doubled tt) i) Source # 

Associated Types

type Rep (SeventhChord r (Doubled tt) i) (a :: SeventhChord r (Doubled tt) i) :: * Source #

Methods

prim :: sing a -> Rep (SeventhChord r (Doubled tt) i) a Source #

pretty :: sing a -> String Source #

type Rep (ChordType 3) (Triad r t i) Source # 
type Rep (ChordType 3) (Triad r t i) = [Int]
type Rep (ChordType 4) (SeventhChord r t i) Source # 
type Rep (ChordType 4) (SeventhChord r t i) = [Int]
type Rep (ChordType 4) (SeventhChord r (Doubled tt) i) Source # 
type Rep (ChordType 4) (SeventhChord r (Doubled tt) i) = [Int]

data Cho c Source #

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 

type family ChordsToPartiture (v :: Vector (ChordType n) l) (d :: Nat) :: Partiture n (l * d) where ... Source #