mezzo-0.3.1.0: Typesafe music composition

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

Mezzo.Model.Rules.RuleSet

Contents

Description

Encapsulation of various musical rule sets that Mezzo can use.

Synopsis

Rule sets

data Free Source #

The types of rule sets implemented. data RuleSetType = Free -- ^ No composition rules. | Classical -- ^ Classical rules. | Strict -- ^ Strict rules.

Constructors

Free 

Instances

RuleSet * Free Source #

No rules.

Associated Types

type MelConstraints (l2 :: Nat) (n :: Nat) (l1 :: Nat) Free (t :: Free) (m1 :: Partiture n l1) (m2 :: Partiture n l2) :: Constraint Source #

type HarmConstraints (n2 :: Nat) (n1 :: Nat) (l :: Nat) Free (t :: Free) (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type NoteConstraints Free (t :: Free) (r :: RootType) (d :: Duration) :: Constraint Source #

type RestConstraints Free (t :: Free) (d :: Duration) :: Constraint Source #

type ChordConstraints (n :: Nat) Free (t :: Free) (c :: ChordType n) (d :: Duration) :: Constraint Source #

type ProgConstraints (k :: KeyType) (l :: Nat) Free (t :: Free) (s :: TimeSignature) (p :: ProgType k l) :: Constraint Source #

type HomConstraints (n2 :: Nat) (n1 :: Nat) (l :: Nat) Free (t :: Free) (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type TriplConstraints Free (t :: Free) (d :: Duration) (r1 :: RootType) (r2 :: RootType) (r3 :: RootType) :: Constraint Source #

type MelConstraints l2 n l1 * Free m1 m2 Source # 
type MelConstraints l2 n l1 * Free m1 m2 = Valid
type HarmConstraints n2 n1 l * Free m1 m2 Source # 
type HarmConstraints n2 n1 l * Free m1 m2 = Valid
type HomConstraints n2 n1 l * Free m1 m2 Source # 
type HomConstraints n2 n1 l * Free m1 m2 = Valid
type ProgConstraints k l * Free s p Source # 
type ProgConstraints k l * Free s p = Valid
type ChordConstraints n * Free c d Source # 
type RestConstraints * Free d Source # 
type NoteConstraints * Free r d Source # 
type TriplConstraints * Free d r1 r2 r3 Source # 
type TriplConstraints * Free d r1 r2 r3 = Valid

data Classical Source #

Constructors

Classical 

Instances

RuleSet * Classical Source #

Classical rules.

Forbids

  • seventh melodic intervals,
  • minor second, major seventh and augmented octave harmonic intervals, and
  • direct motion into perfect intervals on harmonic composition.

Associated Types

type MelConstraints (l2 :: Nat) (n :: Nat) (l1 :: Nat) Classical (t :: Classical) (m1 :: Partiture n l1) (m2 :: Partiture n l2) :: Constraint Source #

type HarmConstraints (n2 :: Nat) (n1 :: Nat) (l :: Nat) Classical (t :: Classical) (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type NoteConstraints Classical (t :: Classical) (r :: RootType) (d :: Duration) :: Constraint Source #

type RestConstraints Classical (t :: Classical) (d :: Duration) :: Constraint Source #

type ChordConstraints (n :: Nat) Classical (t :: Classical) (c :: ChordType n) (d :: Duration) :: Constraint Source #

type ProgConstraints (k :: KeyType) (l :: Nat) Classical (t :: Classical) (s :: TimeSignature) (p :: ProgType k l) :: Constraint Source #

type HomConstraints (n2 :: Nat) (n1 :: Nat) (l :: Nat) Classical (t :: Classical) (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type TriplConstraints Classical (t :: Classical) (d :: Duration) (r1 :: RootType) (r2 :: RootType) (r3 :: RootType) :: Constraint Source #

type MelConstraints l2 n l1 * Classical m1 m2 Source # 
type MelConstraints l2 n l1 * Classical m1 m2 = ValidMelConcat l2 n l1 m1 m2
type HarmConstraints n2 n1 l * Classical m1 m2 Source # 
type HarmConstraints n2 n1 l * Classical m1 m2 = ValidHarmConcat n1 n2 l (Align n2 PitchType n1 l m1 m2)
type HomConstraints n2 n1 l * Classical m1 m2 Source # 
type HomConstraints n2 n1 l * Classical m1 m2 = ValidHomConcat n1 n2 l (Align n2 PitchType n1 l m1 m2)
type ProgConstraints k l * Classical s p Source # 
type ChordConstraints n * Classical c d Source # 
type RestConstraints * Classical d Source # 
type NoteConstraints * Classical r d Source # 
type TriplConstraints * Classical d r1 r2 r3 Source # 
type TriplConstraints * Classical d r1 r2 r3 = Valid

data Strict Source #

Constructors

Strict 

Instances

RuleSet * Strict Source #

Strict rules.

Forbids all of the above (Classical), as well as

  • diminished and augmented melodic intervals,
  • direct motion into perfect intervals on melodic and homophonic composition, and
  • major seventh chords.

Associated Types

type MelConstraints (l2 :: Nat) (n :: Nat) (l1 :: Nat) Strict (t :: Strict) (m1 :: Partiture n l1) (m2 :: Partiture n l2) :: Constraint Source #

type HarmConstraints (n2 :: Nat) (n1 :: Nat) (l :: Nat) Strict (t :: Strict) (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type NoteConstraints Strict (t :: Strict) (r :: RootType) (d :: Duration) :: Constraint Source #

type RestConstraints Strict (t :: Strict) (d :: Duration) :: Constraint Source #

type ChordConstraints (n :: Nat) Strict (t :: Strict) (c :: ChordType n) (d :: Duration) :: Constraint Source #

type ProgConstraints (k :: KeyType) (l :: Nat) Strict (t :: Strict) (s :: TimeSignature) (p :: ProgType k l) :: Constraint Source #

type HomConstraints (n2 :: Nat) (n1 :: Nat) (l :: Nat) Strict (t :: Strict) (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type TriplConstraints Strict (t :: Strict) (d :: Duration) (r1 :: RootType) (r2 :: RootType) (r3 :: RootType) :: Constraint Source #

type MelConstraints l2 n l1 * Strict m1 m2 Source # 
type MelConstraints l2 n l1 * Strict m1 m2 = (ValidMelConcatStrict l2 n l1 m1 m2, ValidMelMatrixMotion l2 n l1 m1 m2)
type HarmConstraints n2 n1 l * Strict m1 m2 Source # 
type HarmConstraints n2 n1 l * Strict m1 m2 = ValidHarmConcat n1 n2 l (Align n2 PitchType n1 l m1 m2)
type HomConstraints n2 n1 l * Strict m1 m2 Source # 
type HomConstraints n2 n1 l * Strict m1 m2 = ValidHarmConcat n1 n2 l (Align n2 PitchType n1 l m1 m2)
type ProgConstraints k l * Strict s p Source # 
type ProgConstraints k l * Strict s p = Valid
type ChordConstraints n * Strict c d Source # 
type RestConstraints * Strict d Source # 
type NoteConstraints * Strict r d Source # 
type TriplConstraints * Strict d r1 r2 r3 Source # 
type TriplConstraints * Strict d r1 r2 r3 = (MelConstraints d 1 d * Strict (FromRoot r1 d) (FromRoot r2 d), MelConstraints d 1 d * Strict (FromRoot r2 d) (FromRoot r3 d))

class RuleSet t Source #

Class of rule sets for a given rule type.

Associated Types

type MelConstraints t (m1 :: Partiture n l1) (m2 :: Partiture n l2) :: Constraint Source #

type HarmConstraints t (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type NoteConstraints t (r :: RootType) (d :: Duration) :: Constraint Source #

type RestConstraints t (d :: Duration) :: Constraint Source #

type ChordConstraints t (c :: ChordType n) (d :: Duration) :: Constraint Source #

type ProgConstraints t (s :: TimeSignature) (p :: ProgType k l) :: Constraint Source #

type HomConstraints t (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type TriplConstraints t (d :: Duration) (r1 :: RootType) (r2 :: RootType) (r3 :: RootType) :: Constraint Source #

Instances

RuleSet * Strict Source #

Strict rules.

Forbids all of the above (Classical), as well as

  • diminished and augmented melodic intervals,
  • direct motion into perfect intervals on melodic and homophonic composition, and
  • major seventh chords.

Associated Types

type MelConstraints (l2 :: Nat) (n :: Nat) (l1 :: Nat) Strict (t :: Strict) (m1 :: Partiture n l1) (m2 :: Partiture n l2) :: Constraint Source #

type HarmConstraints (n2 :: Nat) (n1 :: Nat) (l :: Nat) Strict (t :: Strict) (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type NoteConstraints Strict (t :: Strict) (r :: RootType) (d :: Duration) :: Constraint Source #

type RestConstraints Strict (t :: Strict) (d :: Duration) :: Constraint Source #

type ChordConstraints (n :: Nat) Strict (t :: Strict) (c :: ChordType n) (d :: Duration) :: Constraint Source #

type ProgConstraints (k :: KeyType) (l :: Nat) Strict (t :: Strict) (s :: TimeSignature) (p :: ProgType k l) :: Constraint Source #

type HomConstraints (n2 :: Nat) (n1 :: Nat) (l :: Nat) Strict (t :: Strict) (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type TriplConstraints Strict (t :: Strict) (d :: Duration) (r1 :: RootType) (r2 :: RootType) (r3 :: RootType) :: Constraint Source #

RuleSet * Classical Source #

Classical rules.

Forbids

  • seventh melodic intervals,
  • minor second, major seventh and augmented octave harmonic intervals, and
  • direct motion into perfect intervals on harmonic composition.

Associated Types

type MelConstraints (l2 :: Nat) (n :: Nat) (l1 :: Nat) Classical (t :: Classical) (m1 :: Partiture n l1) (m2 :: Partiture n l2) :: Constraint Source #

type HarmConstraints (n2 :: Nat) (n1 :: Nat) (l :: Nat) Classical (t :: Classical) (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type NoteConstraints Classical (t :: Classical) (r :: RootType) (d :: Duration) :: Constraint Source #

type RestConstraints Classical (t :: Classical) (d :: Duration) :: Constraint Source #

type ChordConstraints (n :: Nat) Classical (t :: Classical) (c :: ChordType n) (d :: Duration) :: Constraint Source #

type ProgConstraints (k :: KeyType) (l :: Nat) Classical (t :: Classical) (s :: TimeSignature) (p :: ProgType k l) :: Constraint Source #

type HomConstraints (n2 :: Nat) (n1 :: Nat) (l :: Nat) Classical (t :: Classical) (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type TriplConstraints Classical (t :: Classical) (d :: Duration) (r1 :: RootType) (r2 :: RootType) (r3 :: RootType) :: Constraint Source #

RuleSet * Free Source #

No rules.

Associated Types

type MelConstraints (l2 :: Nat) (n :: Nat) (l1 :: Nat) Free (t :: Free) (m1 :: Partiture n l1) (m2 :: Partiture n l2) :: Constraint Source #

type HarmConstraints (n2 :: Nat) (n1 :: Nat) (l :: Nat) Free (t :: Free) (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type NoteConstraints Free (t :: Free) (r :: RootType) (d :: Duration) :: Constraint Source #

type RestConstraints Free (t :: Free) (d :: Duration) :: Constraint Source #

type ChordConstraints (n :: Nat) Free (t :: Free) (c :: ChordType n) (d :: Duration) :: Constraint Source #

type ProgConstraints (k :: KeyType) (l :: Nat) Free (t :: Free) (s :: TimeSignature) (p :: ProgType k l) :: Constraint Source #

type HomConstraints (n2 :: Nat) (n1 :: Nat) (l :: Nat) Free (t :: Free) (m1 :: Partiture n1 l) (m2 :: Partiture n2 l) :: Constraint Source #

type TriplConstraints Free (t :: Free) (d :: Duration) (r1 :: RootType) (r2 :: RootType) (r3 :: RootType) :: Constraint Source #

Literal values