mezzo-0.3.1.0: Typesafe music composition

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

Mezzo.Model.Types

Contents

Description

Types modeling basic musical constructs at the type level.

Synopsis

Note properties

data PitchClass Source #

The diatonic pitch class of the note.

Constructors

C 
D 
E 
F 
G 
A 
B 

Instances

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 #

type Rep PitchClass C Source # 
type Rep PitchClass D Source # 
type Rep PitchClass E Source # 
type Rep PitchClass F Source # 
type Rep PitchClass G Source # 
type Rep PitchClass A Source # 
type Rep PitchClass B Source # 

data Accidental Source #

The accidental applied to a note.

Constructors

Natural 
Flat 
Sharp 

Instances

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 #

type Rep Accidental Natural Source # 
type Rep Accidental Flat Source # 
type Rep Accidental Sharp Source # 

data OctaveNum Source #

The octave where the note resides (middle C is Oct4).

Constructors

Oct_1 
Oct0 
Oct1 
Oct2 
Oct3 
Oct4 
Oct5 
Oct6 
Oct7 
Oct8 

Instances

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 #

type Rep OctaveNum Oct_1 Source # 
type Rep OctaveNum Oct0 Source # 
type Rep OctaveNum Oct1 Source # 
type Rep OctaveNum Oct2 Source # 
type Rep OctaveNum Oct3 Source # 
type Rep OctaveNum Oct4 Source # 
type Rep OctaveNum Oct5 Source # 
type Rep OctaveNum Oct6 Source # 
type Rep OctaveNum Oct7 Source # 
type Rep OctaveNum Oct8 Source # 

type Duration = Nat Source #

The duration of the note (a whole note has duration 32).

Singleton types for note properties

data PC pc where Source #

The singleton type for PitchClass.

Constructors

PC :: Primitive pc => PC pc 

data Acc acc where Source #

The singleton type for Accidental.

Constructors

Acc :: Primitive acc => Acc acc 

data Oct oct where Source #

The singleton type for Octave.

Constructors

Oct :: Primitive oct => Oct oct 

data Dur dur where Source #

The singleton type for Duration.

Constructors

Dur :: Primitive dur => Dur dur 

Pitches

data PitchType where Source #

The type of pitches.

Constructors

Pitch :: PitchClass -> Accidental -> OctaveNum -> PitchType

A pitch made up of a pitch class, an accidental and an octave.

Silence :: PitchType

Silence, the pitch of rests.

Instances

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 #

ValidMelConcat l2 0 l1 (None (OptVector PitchType l1)) (None (OptVector PitchType l2)) Source # 
ValidMelMatrixMotion l2 0 l1 (None (OptVector PitchType l1)) (None (OptVector PitchType l2)) Source # 
ValidMelConcatStrict l2 0 l1 (None (OptVector PitchType l1)) (None (OptVector PitchType l2)) Source # 
(ValidHomConcat ((-) n1 1) n2 l ((,) (Partiture ((-) n1 1) l) (Partiture n2 l) vs us), AllSatisfyAll n2 (Voice l) ((:) (Voice l -> Constraint) (ValidHarmDyadsInVectors l v) ([] (Voice l -> Constraint))) us) => ValidHomConcat n1 n2 l ((,) (Vector (Voice l) n1) (Partiture n2 l) ((:--) (Voice l) n1 v vs) us) Source # 
ValidHomConcat 0 n2 l ((,) (Vector (OptVector PitchType l) 0) (Partiture n2 l) (None (OptVector PitchType l)) vs) Source # 
(ValidHarmConcat ((-) n1 1) n2 l ((,) (Partiture ((-) n1 1) l) (Partiture n2 l) vs us), AllSatisfyAll n2 (Voice l) ((:) (Voice l -> Constraint) (ValidHarmDyadsInVectors l v) ((:) (Voice l -> Constraint) (ValidHarmMotionInVectors l l v) ([] (Voice l -> Constraint)))) us) => ValidHarmConcat n1 n2 l ((,) (Vector (Voice l) n1) (Partiture n2 l) ((:--) (Voice l) n1 v vs) us) Source # 
ValidHarmConcat 0 n2 l ((,) (Vector (OptVector PitchType l) 0) (Partiture n2 l) (None (OptVector PitchType l)) vs) Source # 
(ValidMelAppend l2 l1 v1 v2, ValidMelConcat l2 ((-) n 1) l1 vs1 vs2) => ValidMelConcat l2 n l1 ((:--) (Voice l1) n v1 vs1) ((:--) (Voice l2) n v2 vs2) Source # 
(ValidMelMatrixMotion l2 ((-) n 1) l1 vs1 vs2, AllPairsSatisfy' ((-) n 1) (Voice l2) (Voice l1) (ValidMelPitchVectorMotion l2 l1 (Last PitchType l1 v1) (Head PitchType l2 v2)) vs1 vs2) => ValidMelMatrixMotion l2 n l1 ((:--) (OptVector PitchType l1) n v1 vs1) ((:--) (OptVector PitchType l2) n v2 vs2) Source # 
(ValidMelAppendStrict l2 l1 v1 v2, ValidMelConcatStrict l2 ((-) n 1) l1 vs1 vs2) => ValidMelConcatStrict l2 n l1 ((:--) (Voice l1) n v1 vs1) ((:--) (Voice l2) n v2 vs2) 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 #

type Rep PitchType Silence Source # 
type Rep PitchType (Pitch pc acc oct) Source # 
type Rep PitchType (Pitch pc acc oct) = Int

data Pit p where Source #

The singleton type for pitches.

Constructors

Pit :: Primitive p => Pit p 

type family (p :: PitchType) =?= (q :: PitchType) :: Bool where ... Source #

Enharmonic equality of pitches.

Equations

Silence =?= Silence = True 
Silence =?= _ = False 
_ =?= Silence = False 
(Pitch pc acc oct) =?= (Pitch pc acc oct) = True 
(Pitch C Flat o1) =?= (Pitch B Natural o2) = o1 .~. OctSucc o2 
(Pitch C Natural o1) =?= (Pitch B Sharp o2) = o1 .~. OctSucc o2 
(Pitch E Natural oct) =?= (Pitch F Flat oct) = True 
(Pitch E Sharp oct) =?= (Pitch F Natural oct) = True 
(Pitch F Flat oct) =?= (Pitch E Natural oct) = True 
(Pitch F Natural oct) =?= (Pitch E Sharp oct) = True 
(Pitch B Natural o1) =?= (Pitch C Flat o2) = OctSucc o1 .~. o2 
(Pitch B Sharp o1) =?= (Pitch C Natural o2) = OctSucc o1 .~. o2 
(Pitch pc1 Sharp oct) =?= (Pitch pc2 Flat oct) = ClassSucc pc1 .~. pc2 
(Pitch pc1 Flat oct) =?= (Pitch pc2 Sharp oct) = pc1 .~. ClassSucc pc2 
_ =?= _ = False 

type family (p1 :: PitchType) <<=? (p2 :: PitchType) :: Bool where ... infixl 3 Source #

Greater than or equal to for pitches.

Equations

p <<=? p = True 
(Pitch pc1 acc oct) <<=? (Pitch pc2 acc oct) = ClassToNat pc1 <=? ClassToNat pc2 
(Pitch pc acc oct) <<=? (Pitch pc Sharp oct) = True 
(Pitch pc Sharp oct) <<=? (Pitch pc acc oct) = False 
(Pitch pc Flat oct) <<=? (Pitch pc acc oct) = True 
(Pitch pc acc oct) <<=? (Pitch pc Flat oct) = False 
(Pitch E Sharp oct) <<=? (Pitch F Flat oct) = False 
(Pitch F Flat oct) <<=? (Pitch E Sharp oct) = True 
(Pitch B Sharp oct) <<=? (Pitch C Flat oct') = If (NextOct oct oct') False (Pitch B Natural oct <<=? Pitch C Flat oct') 
(Pitch C Flat oct) <<=? (Pitch B Sharp oct') = If (NextOct oct' oct) True (Pitch C Natural oct <<=? Pitch B Sharp oct') 
(Pitch pc1 acc1 oct) <<=? (Pitch pc2 acc2 oct) = ClassToNat pc1 <=? ClassToNat pc2 
(Pitch pc1 acc1 oct1) <<=? (Pitch pc2 acc2 oct2) = OctToNat oct1 <=? OctToNat oct2 
p1 <<=? p2 = PitchToNat p1 <=? PitchToNat p2 

type family (p1 :: PitchType) <<? (p2 :: PitchType) where ... infixl 3 Source #

Greater than for pitches.

Equations

p <<? p = False 
p1 <<? p2 = p1 <<=? p2 

Harmonic types

data Mode Source #

The mode of a key: major or minor.

Constructors

MajorMode 
MinorMode 

Instances

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 #

type Rep Mode MajorMode Source # 
type Rep Mode MinorMode Source # 

data ScaleDegree Source #

The seven scale degrees.

Constructors

I 
II 
III 
IV 
V 
VI 
VII 

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 #

type Rep ScaleDegree I Source # 
type Rep ScaleDegree II Source # 
type Rep ScaleDegree III Source # 
type Rep ScaleDegree IV Source # 
type Rep ScaleDegree V Source # 
type Rep ScaleDegree VI Source # 
type Rep ScaleDegree VII Source # 

data DegreeType Source #

Instances

(IntRep ScaleDegree sd, IntRep Accidental acc, IntRep OctaveNum oct) => Primitive DegreeType (Degree sd acc oct) Source # 

Associated Types

type Rep (Degree sd acc oct) (a :: Degree sd acc oct) :: * Source #

Methods

prim :: sing a -> Rep (Degree sd acc oct) a Source #

pretty :: sing a -> String Source #

type Rep DegreeType (Degree sd acc oct) Source # 
type Rep DegreeType (Degree sd acc oct) = Int

data KeyType Source #

The of a scale, chord or piece.

Instances

(IntRep PitchClass pc, IntRep Accidental acc, BoolRep 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 #

type Rep KeyType (Key pc acc mo) Source # 
type Rep KeyType (Key pc acc mo) = [Int]

data RootType where Source #

The root of a chord.

Constructors

PitchRoot :: PitchType -> RootType

A pitch constructs a diatonic root.

DegreeRoot :: KeyType -> DegreeType -> RootType

A key and a scale degree constructs a scalar root.

Instances

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 #

(IntRep PitchType p, (~) PitchType (RootToPitch (DegreeRoot k deg)) p, Primitive DegreeType deg, Primitive KeyType k) => Primitive RootType (DegreeRoot k deg) Source # 

Associated Types

type Rep (DegreeRoot k deg) (a :: DegreeRoot k deg) :: * Source #

Methods

prim :: sing a -> Rep (DegreeRoot k deg) a Source #

pretty :: sing a -> String Source #

type Rep RootType (PitchRoot p) Source # 
type Rep RootType (DegreeRoot k deg) Source # 
type Rep RootType (DegreeRoot k deg) = Int

data Mod m Source #

The singleton type for Mode.

Constructors

Mod 

data ScaDeg sd Source #

The singleton type for ScaleDegree

Constructors

ScaDeg 

data KeyS k Source #

The singleton type for KeyType.

Constructors

KeyS 

data Deg d Source #

Constructors

Deg 

data Root r where Source #

The singleton type for Root.

Constructors

Root :: Primitive r => Root r 

Instances

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 #

type Rep * (Root (PitchRoot p)) Source # 
type Rep * (Root (PitchRoot p)) = Int

type family RootToPitch (dr :: RootType) :: PitchType where ... Source #

Convert a root to a pitch.

Note: the default octave for scalar roots is Oct2.

Equations

RootToPitch (PitchRoot p) = p 
RootToPitch (DegreeRoot (Key pc acc m) (Degree sd dacc oct)) = HalfStepsUpBy (Pitch pc acc oct) (DegreeOffset m sd dacc) 

type family PitchToNat (p :: PitchType) :: Nat where ... Source #

Convert a pitch to a natural number (equal to its MIDI code).

Equations

PitchToNat Silence = TypeError (Text "Can't convert a rest to a number.") 
PitchToNat (Pitch C Natural Oct_1) = 0 
PitchToNat (Pitch C Sharp Oct_1) = 1 
PitchToNat (Pitch D Flat Oct_1) = 1 
PitchToNat (Pitch C Natural Oct1) = 24 
PitchToNat (Pitch C Natural Oct2) = 36 
PitchToNat (Pitch C Natural Oct3) = 48 
PitchToNat (Pitch C Natural Oct4) = 60 
PitchToNat (Pitch C Natural Oct5) = 72 
PitchToNat (Pitch C Natural Oct6) = 84 
PitchToNat p = 1 + PitchToNat (HalfStepDown p) 

type family Sharpen (r :: RootType) :: RootType where ... Source #

Sharpen a root.

Equations

Sharpen r = PitchRoot (HalfStepUp (RootToPitch r)) 

type family Flatten (r :: RootType) :: RootType where ... Source #

Flatten a root.

Equations

Flatten r = PitchRoot (HalfStepDown (RootToPitch r)) 

type family Dot (d :: Duration) :: Duration where ... Source #

Form a dotted duration.

Equations

Dot 1 = TypeError (Text "Can't have dotted thirty-seconds.") 
Dot n = n + HalfOf n 

type family HalfOf (n :: Nat) :: Nat where ... Source #

Halve a type-level natural.

Equations

HalfOf 0 = 0 
HalfOf 1 = 0 
HalfOf 8 = 4 
HalfOf 32 = 16 
HalfOf n = 1 + HalfOf (n - 2) 

type family FromRoot (r :: RootType) (d :: Nat) :: Partiture 1 d where ... Source #

Create a new partiture with one voice of the given pitch.

Equations

FromRoot r d = (RootToPitch r +*+ d) :-- None 

type family FromSilence (d :: Nat) :: Partiture 1 d where ... Source #

Create a new partiture with one voice of silence.

Equations

FromSilence d = (Silence +*+ d) :-- None 

type family FromTriplet (d :: Nat) (r1 :: RootType) (r2 :: RootType) (r3 :: RootType) :: Partiture 1 ((d + HalfOf d) + HalfOf d) where ... Source #

Create a new partiture with a triplet of three notes.

Equations

FromTriplet d r1 r2 r3 = (FromRoot r1 d +|+ FromRoot r2 (HalfOf d)) +|+ FromRoot r3 (HalfOf d) 

Specialised musical vector types

type Voice l = OptVector PitchType l Source #

A Voice is made up of a sequence of pitch repetitions.

type Partiture n l = Matrix PitchType n l Source #

A Partiture is made up of a fixed number of voices.

Intervals

data IntervalSize Source #

The size of the interval.

Instances

Primitive IntervalSize Unison Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive IntervalSize Second Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive IntervalSize Third Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive IntervalSize Fourth Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive IntervalSize Fifth Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive IntervalSize Sixth Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive IntervalSize Seventh Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive IntervalSize Octave Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

type Rep IntervalSize Unison Source # 
type Rep IntervalSize Second Source # 
type Rep IntervalSize Third Source # 
type Rep IntervalSize Fourth Source # 
type Rep IntervalSize Fifth Source # 
type Rep IntervalSize Sixth Source # 
type Rep IntervalSize Seventh Source # 
type Rep IntervalSize Octave Source # 

data IntervalClass Source #

The class of the interval.

Constructors

Maj 
Perf 
Min 
Aug 
Dim 

Instances

Primitive IntervalClass Maj Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive IntervalClass Perf Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive IntervalClass Min Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive IntervalClass Aug Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

Primitive IntervalClass Dim Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #

type Rep IntervalClass Maj Source # 
type Rep IntervalClass Perf Source # 
type Rep IntervalClass Min Source # 
type Rep IntervalClass Aug Source # 
type Rep IntervalClass Dim Source # 

data IntervalType where Source #

The type of intervals.

Constructors

Interval :: IntervalClass -> IntervalSize -> IntervalType

An interval smaller than 13 semitones, where musical rules can still be enforced.

Compound :: IntervalType

An interval larger than 13 semitones, which is large enough so that dissonance effects are not significant.

Instances

(FunRep IntervalClass Int Int ic, IntRep IntervalSize is) => Primitive IntervalType (Interval ic is) Source # 

Associated Types

type Rep (Interval ic is) (a :: Interval ic is) :: * Source #

Methods

prim :: sing a -> Rep (Interval ic is) a Source #

pretty :: sing a -> String Source #

type Rep IntervalType (Interval ic is) Source # 
type Rep IntervalType (Interval ic is) = Int

type family MakeInterval (p1 :: PitchType) (p2 :: PitchType) :: IntervalType where ... Source #

Make an interval from two arbitrary pitches.

Equations

MakeInterval Silence Silence = TypeError (Text "Can't make intervals from rests.") 
MakeInterval Silence p2 = TypeError (Text "Can't make intervals from rests.") 
MakeInterval p1 Silence = TypeError (Text "Can't make intervals from rests.") 
MakeInterval p1 p2 = If (p1 <<=? p2) (MakeIntervalOrd p1 p2) (MakeIntervalOrd p2 p1) 

Singleton types for interval properties

data IC ic Source #

The singleton type for IntervalClass.

Constructors

IC 

data IS is Source #

The singleton type for IntervalSize.

Constructors

IS 

data Intv i Source #

The singleton type for IntervalType.

Constructors

Intv 

Operations

type family OctPred (o :: OctaveNum) :: OctaveNum where ... Source #

Decrement an octave.

Equations

OctPred o = DecreaseOctave o 1 

type family OctSucc (o :: OctaveNum) :: OctaveNum where ... Source #

Increment an octave.

Equations

OctSucc o = IncreaseOctave o 1 

type family HalfStepsUpBy (p :: PitchType) (n :: Nat) :: PitchType where ... Source #

Move a pitch up by the specified number of semitones.

Equations

HalfStepsUpBy p 0 = p 
HalfStepsUpBy p n = HalfStepUp (HalfStepsUpBy p (n - 1)) 

type family HalfStepsDownBy (p :: PitchType) (n :: Nat) :: PitchType where ... Source #

Move a pitch down by the specified number of semitones.

Equations

HalfStepsDownBy p 0 = p 
HalfStepsDownBy p n = HalfStepDown (HalfStepsDownBy p (n - 1)) 

type family RaiseBy (p :: PitchType) (i :: IntervalType) :: PitchType where ... Source #

Raise a pitch by an interval.

Equations

RaiseBy Silence _ = Silence 
RaiseBy _ Compound = TypeError (Text "Can't shift by compound interval") 
RaiseBy p (Interval Min is) = HalfStepDown (HalfStepsUpBy p (IntervalWidth (Interval Min is) + 1)) 
RaiseBy p (Interval Dim is) = HalfStepDown (HalfStepsUpBy p (IntervalWidth (Interval Dim is) + 1)) 
RaiseBy p i = HalfStepsUpBy p (IntervalWidth i) 

type family LowerBy (p :: PitchType) (i :: IntervalType) :: PitchType where ... Source #

Lower a pitch by an interval.

Equations

LowerBy Silence _ = Silence 
LowerBy _ Compound = TypeError (Text "Can't shift by compound interval") 
LowerBy p (Interval Maj is) = HalfStepUp (HalfStepsDownBy p (IntervalWidth (Interval Maj is) + 1)) 
LowerBy p (Interval Aug is) = HalfStepUp (HalfStepsDownBy p (IntervalWidth (Interval Aug is) + 1)) 
LowerBy p i = HalfStepsDownBy p (IntervalWidth i) 

type family RaiseAllBy (ps :: Voice l) (i :: IntervalType) :: Voice l where ... Source #

Raise all pitches in a voice by an interval.

Equations

RaiseAllBy End _ = End 
RaiseAllBy ((p :* d) :- ps) i = (RaiseBy p i :* d) :- RaiseAllBy ps i 

type family LowerAllBy (ps :: Voice l) (i :: IntervalType) :: Voice l where ... Source #

Lower all pitches in a voice by an interval.

Equations

LowerAllBy End _ = End 
LowerAllBy ((p :* d) :- ps) i = (LowerBy p i :* d) :- LowerAllBy ps i 

type family RaiseAllBy' (ps :: Vector PitchType n) (i :: IntervalType) :: Vector PitchType n where ... Source #

Raise multiple pitches by an interval.

Equations

RaiseAllBy' None _ = None 
RaiseAllBy' (p :-- ps) i = RaiseBy p i :-- RaiseAllBy' ps i 

type family LowerAllBy' (ps :: Vector PitchType n) (i :: IntervalType) :: Vector PitchType n where ... Source #

Lower multiple pitches by an interval.

Equations

LowerAllBy' None _ = None 
LowerAllBy' (p :-- ps) i = LowerBy p i :-- LowerAllBy' ps i 

type family RaiseByOct (p :: PitchType) :: PitchType where ... Source #

Raise a pitch by an octave.

type family LowerByOct (p :: PitchType) :: PitchType where ... Source #

Lower a pitch by an octave.

type family RaiseAllByOct (ps :: Voice l) :: Voice l where ... Source #

type family TransposeUpBy (p :: Partiture n l) (i :: IntervalType) :: Partiture n l where ... Source #

Transpose a partiture up by the given interval.

Equations

TransposeUpBy _ Compound = TypeError (Text "Can't transpose by compound interval.") 
TransposeUpBy None i = None 
TransposeUpBy (v :-- vs) i = RaiseAllBy v i :-- TransposeUpBy vs i 

type family TransposeDownBy (p :: Partiture n l) (i :: IntervalType) :: Partiture n l where ... Source #

Transpose a partiture down by the given interval.

Equations

TransposeDownBy _ Compound = TypeError (Text "Can't transpose by compound interval.") 
TransposeDownBy None i = None 
TransposeDownBy (v :-- vs) i = LowerAllBy v i :-- TransposeDownBy vs i 

Orphan instances

KnownNat n => Primitive Nat n Source # 

Associated Types

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

Methods

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

pretty :: sing a -> String Source #