| Copyright | (c) Dima Szamozvancev |
|---|---|
| License | MIT |
| Maintainer | ds709@cam.ac.uk |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Mezzo.Model.Harmony.Chords
Contents
Description
Types and type functions modelling harmonic chords.
- data DyadType
- data TriadType
- data TetradType
- data Inversion
- data DyaType t = DyaType
- data TriType t = TriType
- data TetType t = TetType
- data Inv t = Inv
- type family InvertChord (c :: ChordType n) :: ChordType n where ...
- data ChordType :: Nat -> Type where
- data Cho c = Cho
- type family FromChord (c :: ChordType n) (l :: Nat) :: Partiture n l where ...
Chords
The type of a dyad.
Constructors
| MinThird | |
| MajThird | |
| PerfFourth | |
| PerfFifth | |
| PerfOct |
Instances
| Primitive DyadType MinThird Source # | |
| Primitive DyadType MajThird Source # | |
| Primitive DyadType PerfFourth Source # | |
| Primitive DyadType PerfFifth Source # | |
| Primitive DyadType PerfOct 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 # | |
The type of a triad.
Instances
| Primitive TriadType MajTriad Source # | |
| Primitive TriadType MinTriad Source # | |
| Primitive TriadType AugTriad Source # | |
| Primitive TriadType DimTriad Source # | |
| FunRep DyadType Int [Int] c => Primitive TriadType (DoubledD c) 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 # | |
data TetradType Source #
The type of a tetrad.
Instances
| Primitive TetradType MajSeventh Source # | |
| Primitive TetradType MajMinSeventh Source # | |
| Primitive TetradType MinSeventh Source # | |
| Primitive TetradType HalfDimSeventh Source # | |
| Primitive TetradType DimSeventh Source # | |
| FunRep TriadType Int [Int] c => Primitive TetradType (DoubledT c) 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 # | |
The inversion of a chord.
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 # | |
| (IntRep RootType r, FunRep TriadType Int [Int] t, FunRep Inversion [Int] [Int] i) => Primitive (ChordType 3) (Triad r t i) Source # | |
| (IntRep RootType r, FunRep DyadType Int [Int] dt, FunRep Inversion [Int] [Int] i) => Primitive (ChordType 3) (Triad r (DoubledD dt) i) Source # | |
| (IntRep RootType r, FunRep TetradType Int [Int] t, FunRep Inversion [Int] [Int] i) => Primitive (ChordType 4) (Tetrad r t i) Source # | |
| (IntRep RootType r, FunRep TriadType Int [Int] tt, FunRep Inversion [Int] [Int] i) => Primitive (ChordType 4) (Tetrad r (DoubledT tt) i) Source # | |
| type Rep (ChordType 2) (Dyad r t i) Source # | |
| type Rep (ChordType 3) (Triad r t i) Source # | |
| type Rep (ChordType 3) (Triad r (DoubledD dt) i) Source # | |
| type Rep (ChordType 4) (Tetrad r t i) Source # | |
| type Rep (ChordType 4) (Tetrad r (DoubledT tt) i) Source # | |