mezzo-0.3.1.0: Typesafe music composition

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

Mezzo.Model.Music

Contents

Description

Algebraic description of music with type-level constraints.

Synopsis

Music

data Music :: forall n l t k r. Signature t k r -> Partiture n l -> Type where Source #

A piece of music consisting of parallel and sequential composition of notes and rests, subject to constraints.

Currently enforced constraints are:

  • Height (number of voices) of two sequentially composed pieces must be equal.
  • Width (number of temporal units) of two parallelly composed pieces must be equal.
  • Sequentially composed voices cannot have any augmented, diminished or seventh leaps.
  • Parallelly composed pieces cannot have any minor second or major seventh harmonic intervals.
  • Music must not contain parallel or concealed unisons, fifths or octaves.

Constructors

(:|:) :: ValidMel s m1 m2 => Music s m1 -> Music s m2 -> Music s (m1 +|+ m2) infixl 3

Sequential or melodic composition of music.

(:-:) :: ValidHarm s m1 m2 => Music s m1 -> Music s m2 -> Music s (m1 +-+ m2) infixl 4

Parallel or harmonic composition of music.

Note :: ValidNote s r d => Root r -> Dur d -> Music s (FromRoot r d)

A note specified by a pitch and a duration.

Rest :: ValidRest s d => Dur d -> Music s (FromSilence d)

A rest specified by a duration.

Chord :: ValidChord s c d => Cho c -> Dur d -> Music s (FromChord c d)

A chord specified by a chord type and a duration.

Progression :: ValidProg r t p => Prog p -> Music (Sig :: Signature t k r) (FromProg p t)

A progression specified by a time signature, and its progression schema.

Homophony :: ValidHom s m a => Music s m -> Music s a -> Music s (m +-+ a)

A homophonic composition with a melody line and an accompaniment.

Triplet :: ValidTripl s d r1 r2 r3 => Dur d -> Root r1 -> Root r2 -> Root r3 -> Music s (FromTriplet d r1 r2 r3)

A triplet with a nominal duration and three pitches.

Instances

Show (Music n l t k r s m) Source # 

Methods

showsPrec :: Int -> Music n l t k r s m -> ShowS #

show :: Music n l t k r s m -> String #

showList :: [Music n l t k r s m] -> ShowS #

data Signature t k ruleset Source #

Properties of a musical piece: the time signature, the key signature and rule set.

Constructors

Sig 

Constraints

type ValidNote s ro d = (NoteConstraints r ro d, IntRep ro, Primitive d) Source #

Ensures that the note is valid.

type ValidRest s d = (RestConstraints r d, Primitive d) Source #

Ensures that the rest is valid.

type ValidChord s c d = (ChordConstraints r c d, IntListRep c, Primitive n, Primitive d) Source #

Ensures that the chord is valid.

type ValidProg r t p = (ProgConstraints r t p, IntLListRep p, IntRep t, KnownNat t) Source #

Ensures that a progression is valid.

type ValidHom s m a = HomConstraints r m a Source #

Ensures that a homophonic composition is valid.

type ValidMel s m1 m2 = MelConstraints r m1 m2 Source #

Ensures that two pieces of music can be composed sequentially.

type ValidHarm s m1 m2 = HarmConstraints r m1 m2 Source #

Ensures that two pieces of music can be composed in parallel.

type ValidTripl s d r1 r2 r3 = (TriplConstraints r d r1 r2 r3, IntRep r1, IntRep r2, IntRep r3, Primitive d, Primitive (HalfOf d), NoteConstraints r r1 d, NoteConstraints r r2 (HalfOf d), NoteConstraints r r3 (HalfOf d)) Source #

Ensures that a triplet is valid.