mezzo-0.1.0.0: Typesafe music composition

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

Mezzo.Model.Reify

Contents

Description

Class of types which can be reified at the term level.

Synopsis

Documentation

class Primitive a where Source #

Class of types which can have a primitive representation at runtime.

Minimal complete definition

prim, pretty

Associated Types

type Rep a Source #

The type of the primitive representation.

Methods

prim :: sing a -> Rep a Source #

Convert a singleton of the type into its primitive representation.

pretty :: sing a -> String Source #

Pretty print a singleton of the type.

Instances

Primitive ScaleDegree I Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive ScaleDegree II Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive ScaleDegree III Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive ScaleDegree IV Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive ScaleDegree V Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive ScaleDegree VI Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive ScaleDegree VII Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive Mode MajorMode Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive Mode MinorMode Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive PitchType Silence Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive OctaveNum Oct_1 Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive OctaveNum Oct0 Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive OctaveNum Oct1 Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive OctaveNum Oct2 Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive OctaveNum Oct3 Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive OctaveNum Oct4 Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive OctaveNum Oct5 Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive OctaveNum Oct6 Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive OctaveNum Oct7 Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive OctaveNum Oct8 Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive Accidental Natural Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive Accidental Flat Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive Accidental Sharp Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive PitchClass C Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive PitchClass D Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive PitchClass E Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive PitchClass F Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive PitchClass G Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive PitchClass A Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive PitchClass B Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

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 #

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 #

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 #

IntRep PitchType p => Primitive RootType (PitchRoot p) Source # 

Associated Types

type Rep (PitchRoot p) (a :: PitchRoot p) :: * Source #

Methods

prim :: sing a -> Rep (PitchRoot p) 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 #

(IntRep PitchClass pc, IntRep Accidental acc, IntRep Mode mo) => Primitive KeyType (Key pc acc mo) Source # 

Associated Types

type Rep (Key pc acc mo) (a :: Key pc acc mo) :: * Source #

Methods

prim :: sing a -> Rep (Key pc acc mo) a Source #

pretty :: sing a -> String Source #

(IntRep PitchClass pc, IntRep Accidental acc, IntRep OctaveNum oct) => Primitive PitchType (Pitch pc acc oct) Source # 

Associated Types

type Rep (Pitch pc acc oct) (a :: Pitch pc acc oct) :: * Source #

Methods

prim :: sing a -> Rep (Pitch pc acc oct) a Source #

pretty :: sing a -> String Source #

IntRep PitchType p => Primitive * (Root (PitchRoot p)) Source # 

Associated Types

type Rep (Root (PitchRoot p)) (a :: Root (PitchRoot p)) :: * Source #

Methods

prim :: sing a -> Rep (Root (PitchRoot p)) a Source #

pretty :: sing a -> String Source #

(IntRep PitchType p, (~) PitchType (RootToPitch (DegreeRoot k sd)) p, Primitive ScaleDegree sd) => Primitive * (Root (DegreeRoot k sd)) Source # 

Associated Types

type Rep (Root (DegreeRoot k sd)) (a :: Root (DegreeRoot k sd)) :: * Source #

Methods

prim :: sing a -> Rep (Root (DegreeRoot k sd)) 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 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 IntRep t = (Primitive t, Rep t ~ Int) Source #

Primitive types with integer representations.

type IntListRep t = (Primitive t, Rep t ~ [Int]) Source #

Primitive types with integer list representations.

type FunRep a b t = (Primitive t, Rep t ~ (a -> b)) Source #

Primitive types with function representations from type a to type b.

Orphan instances

Primitive k t => Show (sing t) Source # 

Methods

showsPrec :: Int -> sing t -> ShowS #

show :: sing t -> String #

showList :: [sing t] -> ShowS #