mezzo-0.3.0.0: Typesafe music composition

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

Mezzo.Model.Errors

Description

Types and functions for handling and displaying composition errors.

Synopsis

Documentation

type PitchPair = (PitchType, PitchType) Source #

A pair of pitches.

data DyadPair Source #

A pair of dyads (pair of pairs of pitches).

Constructors

DyP PitchPair PitchPair 

type family DyPair p1 p2 q1 q2 :: DyadPair where ... Source #

Create dyad pair from four pitches.

Equations

DyPair p1 p2 q1 q2 = DyP '(p1, p2) '(q1, q2) 

type family PpPC (pc :: PitchClass) :: ErrorMessage where ... Source #

Print pitch class type.

Equations

PpPC C = Text "C" 
PpPC D = Text "D" 
PpPC E = Text "E" 
PpPC F = Text "F" 
PpPC G = Text "G" 
PpPC A = Text "A" 
PpPC B = Text "B" 

type family PpAcc (acc :: Accidental) :: ErrorMessage where ... Source #

Print accidental type.

Equations

PpAcc Natural = Text "" 
PpAcc Sharp = Text "#" 
PpAcc Flat = Text "b" 

type family PpOct (oct :: OctaveNum) :: ErrorMessage where ... Source #

Print octave type.

Equations

PpOct Oct_1 = Text "_5" 
PpOct Oct0 = Text "_4" 
PpOct Oct1 = Text "_3" 
PpOct Oct2 = Text "__" 
PpOct Oct3 = Text "_" 
PpOct Oct4 = Text "" 
PpOct Oct5 = Text "'" 
PpOct Oct6 = Text "''" 
PpOct Oct7 = Text "'3" 
PpOct Oct8 = Text "'4" 

type family PpPitch (p :: PitchType) :: ErrorMessage where ... Source #

Print pitch type.

Equations

PpPitch (Pitch pc acc oct) = (PpPC pc :<>: PpAcc acc) :<>: PpOct oct 
PpPitch Silence = Text "Rest" 

type family PpPitchPair (pp :: PitchPair) :: ErrorMessage where ... Source #

Print pitch pair.

Equations

PpPitchPair '(p1, p2) = (PpPitch p1 :<>: Text " and ") :<>: PpPitch p2 

type family PpDyadPair (dp :: DyadPair) :: ErrorMessage where ... Source #

Print dyad pair.

Equations

PpDyadPair (DyP d1 d2) = (PpPitchPair d1 :<>: Text ", then ") :<>: PpPitchPair d2 

type family PitchError (t :: Symbol) (p :: PitchType) where ... Source #

Create an error message with a given text and pitch.

Equations

PitchError t p = TypeError (Text t :<>: PpPitch p) 

type family PitchPairError (t :: Symbol) (p :: PitchPair) where ... Source #

Create an error message with a given text and pair of pitches.

type family MotionError (t :: Symbol) (d :: DyadPair) where ... Source #

Create an error message with the given text and pair of dyads.

Equations

MotionError t p = TypeError (Text t :<>: PpDyadPair p) 

type family ChordError (t1 :: Symbol) (r :: RootType) (t2 :: Symbol) where ... Source #

Create an error message with the given text and chord root.

Equations

ChordError t1 r t2 = TypeError ((Text t1 :<>: PpPitch (RootToPitch r)) :<>: Text t2)