proto-voice-model-0.1.0.0
Safe HaskellSafe-Inferred
LanguageGHC2021

PVGrammar

Description

This module contains common datatypes and functions specific to the protovoice grammar. In a protovoice derivations, slices are multisets of notes while transitions contain connections between these notes.

Code that is specific to parsing can be found in PVGrammar.Parse, while generative code is located in PVGrammar.Generate.

Synopsis

Inner Structure Types

Slices: Notes

newtype Notes n Source #

The content type of slices in the protovoice model. Contains a multiset of pitches, representing the notes in a slice.

Constructors

Notes (MultiSet n) 

Instances

Instances details
(Notation n, Eq n, Hashable n) => FromJSON (Notes n) Source # 
Instance details

Defined in PVGrammar

Generic (Notes n) Source # 
Instance details

Defined in PVGrammar

Associated Types

type Rep (Notes n) :: Type -> Type #

Methods

from :: Notes n -> Rep (Notes n) x #

to :: Rep (Notes n) x -> Notes n #

Notation n => Show (Notes n) Source # 
Instance details

Defined in PVGrammar

Methods

showsPrec :: Int -> Notes n -> ShowS #

show :: Notes n -> String #

showList :: [Notes n] -> ShowS #

NFData n => NFData (Notes n) Source # 
Instance details

Defined in PVGrammar

Methods

rnf :: Notes n -> () #

Eq n => Eq (Notes n) Source # 
Instance details

Defined in PVGrammar

Methods

(==) :: Notes n -> Notes n -> Bool #

(/=) :: Notes n -> Notes n -> Bool #

Ord n => Ord (Notes n) Source # 
Instance details

Defined in PVGrammar

Methods

compare :: Notes n -> Notes n -> Ordering #

(<) :: Notes n -> Notes n -> Bool #

(<=) :: Notes n -> Notes n -> Bool #

(>) :: Notes n -> Notes n -> Bool #

(>=) :: Notes n -> Notes n -> Bool #

max :: Notes n -> Notes n -> Notes n #

min :: Notes n -> Notes n -> Notes n #

Hashable n => Hashable (Notes n) Source # 
Instance details

Defined in PVGrammar

Methods

hashWithSalt :: Int -> Notes n -> Int #

hash :: Notes n -> Int #

type Rep (Notes n) Source # 
Instance details

Defined in PVGrammar

type Rep (Notes n) = D1 ('MetaData "Notes" "PVGrammar" "proto-voice-model-0.1.0.0-IpbUkUcWDicKjQK7SlZCoP" 'True) (C1 ('MetaCons "Notes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MultiSet n))))

innerNotes :: StartStop (Notes n) -> [StartStop n] Source #

Return the notes or start/stop symbols inside a slice. This is useful to get all objects that an Edge can connect to.

Transitions: Sets of Obligatory Edges

Transitions contain two kinds of edges, regular edges and passing edges.

data Edges n Source #

The content type of transitions in the protovoice model. Contains a multiset of regular edges and a multiset of passing edges. The represented edges are those that are definitely used later on. Edges that are not used are dropped before creating a child transition. A transition that contains passing edges cannot be frozen.

Constructors

Edges 

Fields

Instances

Instances details
(Eq n, Hashable n, Notation n) => FromJSON (Edges n) Source # 
Instance details

Defined in PVGrammar

(Hashable n, Eq n) => Monoid (Edges n) Source # 
Instance details

Defined in PVGrammar

Methods

mempty :: Edges n #

mappend :: Edges n -> Edges n -> Edges n #

mconcat :: [Edges n] -> Edges n #

(Hashable n, Eq n) => Semigroup (Edges n) Source # 
Instance details

Defined in PVGrammar

Methods

(<>) :: Edges n -> Edges n -> Edges n #

sconcat :: NonEmpty (Edges n) -> Edges n #

stimes :: Integral b => b -> Edges n -> Edges n #

Generic (Edges n) Source # 
Instance details

Defined in PVGrammar

Associated Types

type Rep (Edges n) :: Type -> Type #

Methods

from :: Edges n -> Rep (Edges n) x #

to :: Rep (Edges n) x -> Edges n #

Notation n => Show (Edges n) Source # 
Instance details

Defined in PVGrammar

Methods

showsPrec :: Int -> Edges n -> ShowS #

show :: Edges n -> String #

showList :: [Edges n] -> ShowS #

NFData n => NFData (Edges n) Source # 
Instance details

Defined in PVGrammar

Methods

rnf :: Edges n -> () #

Eq n => Eq (Edges n) Source # 
Instance details

Defined in PVGrammar

Methods

(==) :: Edges n -> Edges n -> Bool #

(/=) :: Edges n -> Edges n -> Bool #

Ord n => Ord (Edges n) Source # 
Instance details

Defined in PVGrammar

Methods

compare :: Edges n -> Edges n -> Ordering #

(<) :: Edges n -> Edges n -> Bool #

(<=) :: Edges n -> Edges n -> Bool #

(>) :: Edges n -> Edges n -> Bool #

(>=) :: Edges n -> Edges n -> Bool #

max :: Edges n -> Edges n -> Edges n #

min :: Edges n -> Edges n -> Edges n #

Hashable n => Hashable (Edges n) Source # 
Instance details

Defined in PVGrammar

Methods

hashWithSalt :: Int -> Edges n -> Int #

hash :: Edges n -> Int #

type Rep (Edges n) Source # 
Instance details

Defined in PVGrammar

type Rep (Edges n) = D1 ('MetaData "Edges" "PVGrammar" "proto-voice-model-0.1.0.0-IpbUkUcWDicKjQK7SlZCoP" 'False) (C1 ('MetaCons "Edges" 'PrefixI 'True) (S1 ('MetaSel ('Just "edgesReg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Edge n))) :*: S1 ('MetaSel ('Just "edgesPass") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MultiSet (InnerEdge n)))))

topEdges :: Hashable n => Edges n Source #

The starting transition of a derivation (⋊——⋉).

type Edge n = (StartStop n, StartStop n) Source #

A proto-voice edge between two nodes (i.e. notes or start/stop symbols).

type InnerEdge n = (n, n) Source #

A proto-voice edge between two notes (excluding start/stop symbols).

Generative Operations

Freeze

data Freeze Source #

Represents a freeze operation. Since this just ties all remaining edges (which must all be repetitions) no decisions have to be encoded.

Constructors

FreezeOp 

Instances

Instances details
FromJSON Freeze Source # 
Instance details

Defined in PVGrammar

Generic Freeze Source # 
Instance details

Defined in PVGrammar

Associated Types

type Rep Freeze :: Type -> Type #

Methods

from :: Freeze -> Rep Freeze x #

to :: Rep Freeze x -> Freeze #

Show Freeze Source # 
Instance details

Defined in PVGrammar

NFData Freeze Source # 
Instance details

Defined in PVGrammar

Methods

rnf :: Freeze -> () #

Eq Freeze Source # 
Instance details

Defined in PVGrammar

Methods

(==) :: Freeze -> Freeze -> Bool #

(/=) :: Freeze -> Freeze -> Bool #

Ord Freeze Source # 
Instance details

Defined in PVGrammar

type Rep Freeze Source # 
Instance details

Defined in PVGrammar

type Rep Freeze = D1 ('MetaData "Freeze" "PVGrammar" "proto-voice-model-0.1.0.0-IpbUkUcWDicKjQK7SlZCoP" 'False) (C1 ('MetaCons "FreezeOp" 'PrefixI 'False) (U1 :: Type -> Type))

Split

data Split n Source #

Encodes the decisions made in a split operation. Contains a list of elaborations for every parent edge and note. Each elaboration contains the child pitch, and the corresponding ornament. For every produced edge, a decisions is made whether to keep it or not.

Constructors

SplitOp 

Fields

  • splitReg :: !(Map (Edge n) [(n, DoubleOrnament)])

    Maps every regular edge to a list of ornamentations.

  • splitPass :: !(Map (InnerEdge n) [(n, PassingOrnament)])

    Maps every passing edge to a passing tone. Since every passing edge is elaborated exactly once but there can be several instances of the same edge in a transition, the "same" edge can be elaborated with several passing notes, one for each instance of the edge.

  • fromLeft :: !(Map n [(n, RightOrnament)])

    Maps notes from the left parent slice to lists of ornamentations.

  • fromRight :: !(Map n [(n, LeftOrnament)])

    Maps notes from the right parent slice to lists of ornamentations.

  • keepLeft :: !(HashSet (Edge n))

    The set of regular edges to keep in the left child transition.

  • keepRight :: !(HashSet (Edge n))

    The set of regular edges to keep in the right child transition.

  • passLeft :: !(MultiSet (InnerEdge n))

    Contains the new passing edges introduced in the left child transition (excluding those passed down from the parent transition).

  • passRight :: !(MultiSet (InnerEdge n))

    Contains the new passing edges introduced in the right child transition (excluding those passed down from the parent transition).

Instances

Instances details
(Notation n, Ord n, Hashable n) => FromJSON (Split n) Source # 
Instance details

Defined in PVGrammar

(Ord n, Hashable n) => Monoid (Split n) Source # 
Instance details

Defined in PVGrammar

Methods

mempty :: Split n #

mappend :: Split n -> Split n -> Split n #

mconcat :: [Split n] -> Split n #

(Ord n, Hashable n) => Semigroup (Split n) Source # 
Instance details

Defined in PVGrammar

Methods

(<>) :: Split n -> Split n -> Split n #

sconcat :: NonEmpty (Split n) -> Split n #

stimes :: Integral b => b -> Split n -> Split n #

Generic (Split n) Source # 
Instance details

Defined in PVGrammar

Associated Types

type Rep (Split n) :: Type -> Type #

Methods

from :: Split n -> Rep (Split n) x #

to :: Rep (Split n) x -> Split n #

Notation n => Show (Split n) Source # 
Instance details

Defined in PVGrammar

Methods

showsPrec :: Int -> Split n -> ShowS #

show :: Split n -> String #

showList :: [Split n] -> ShowS #

NFData n => NFData (Split n) Source # 
Instance details

Defined in PVGrammar

Methods

rnf :: Split n -> () #

Eq n => Eq (Split n) Source # 
Instance details

Defined in PVGrammar

Methods

(==) :: Split n -> Split n -> Bool #

(/=) :: Split n -> Split n -> Bool #

Ord n => Ord (Split n) Source # 
Instance details

Defined in PVGrammar

Methods

compare :: Split n -> Split n -> Ordering #

(<) :: Split n -> Split n -> Bool #

(<=) :: Split n -> Split n -> Bool #

(>) :: Split n -> Split n -> Bool #

(>=) :: Split n -> Split n -> Bool #

max :: Split n -> Split n -> Split n #

min :: Split n -> Split n -> Split n #

type Rep (Split n) Source # 
Instance details

Defined in PVGrammar

data DoubleOrnament Source #

Two-sided ornament types (two parents).

Constructors

FullNeighbor

a full neighbor note

FullRepeat

a repetition of both parents (which have the same pitch)

LeftRepeatOfRight

a repetition of the right parent

RightRepeatOfLeft

a repetitions of the left parent

RootNote

a note inserted at the top of the piece (between ⋊ and ⋉)

Instances

Instances details
FromJSON DoubleOrnament Source # 
Instance details

Defined in PVGrammar

ToJSON DoubleOrnament Source # 
Instance details

Defined in PVGrammar

Generic DoubleOrnament Source # 
Instance details

Defined in PVGrammar

Associated Types

type Rep DoubleOrnament :: Type -> Type #

Show DoubleOrnament Source # 
Instance details

Defined in PVGrammar

NFData DoubleOrnament Source # 
Instance details

Defined in PVGrammar

Methods

rnf :: DoubleOrnament -> () #

Eq DoubleOrnament Source # 
Instance details

Defined in PVGrammar

Ord DoubleOrnament Source # 
Instance details

Defined in PVGrammar

type Rep DoubleOrnament Source # 
Instance details

Defined in PVGrammar

type Rep DoubleOrnament = D1 ('MetaData "DoubleOrnament" "PVGrammar" "proto-voice-model-0.1.0.0-IpbUkUcWDicKjQK7SlZCoP" 'False) ((C1 ('MetaCons "FullNeighbor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FullRepeat" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LeftRepeatOfRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RightRepeatOfLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RootNote" 'PrefixI 'False) (U1 :: Type -> Type))))

isRepetitionOnLeft :: DoubleOrnament -> Bool Source #

Returns True if the child repeats the left parent

isRepetitionOnRight :: DoubleOrnament -> Bool Source #

Returns True if the child repeats the right parent

data PassingOrnament Source #

Types of passing notes (two parents).

Constructors

PassingMid

a connecting passing note (step to both parents)

PassingLeft

a step from the left parent

PassingRight

a step from the right parent

Instances

Instances details
FromJSON PassingOrnament Source # 
Instance details

Defined in PVGrammar

ToJSON PassingOrnament Source # 
Instance details

Defined in PVGrammar

Generic PassingOrnament Source # 
Instance details

Defined in PVGrammar

Associated Types

type Rep PassingOrnament :: Type -> Type #

Show PassingOrnament Source # 
Instance details

Defined in PVGrammar

NFData PassingOrnament Source # 
Instance details

Defined in PVGrammar

Methods

rnf :: PassingOrnament -> () #

Eq PassingOrnament Source # 
Instance details

Defined in PVGrammar

Ord PassingOrnament Source # 
Instance details

Defined in PVGrammar

type Rep PassingOrnament Source # 
Instance details

Defined in PVGrammar

type Rep PassingOrnament = D1 ('MetaData "PassingOrnament" "PVGrammar" "proto-voice-model-0.1.0.0-IpbUkUcWDicKjQK7SlZCoP" 'False) (C1 ('MetaCons "PassingMid" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PassingLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PassingRight" 'PrefixI 'False) (U1 :: Type -> Type)))

data LeftOrnament Source #

Types of single-sided ornaments left of the parent (child-parent)

[ ] [p]
    /
  [c]

Constructors

LeftNeighbor

an incomplete left neighbor

LeftRepeat

an incomplete left repetition

Instances

Instances details
FromJSON LeftOrnament Source # 
Instance details

Defined in PVGrammar

ToJSON LeftOrnament Source # 
Instance details

Defined in PVGrammar

Generic LeftOrnament Source # 
Instance details

Defined in PVGrammar

Associated Types

type Rep LeftOrnament :: Type -> Type #

Show LeftOrnament Source # 
Instance details

Defined in PVGrammar

NFData LeftOrnament Source # 
Instance details

Defined in PVGrammar

Methods

rnf :: LeftOrnament -> () #

Eq LeftOrnament Source # 
Instance details

Defined in PVGrammar

Ord LeftOrnament Source # 
Instance details

Defined in PVGrammar

type Rep LeftOrnament Source # 
Instance details

Defined in PVGrammar

type Rep LeftOrnament = D1 ('MetaData "LeftOrnament" "PVGrammar" "proto-voice-model-0.1.0.0-IpbUkUcWDicKjQK7SlZCoP" 'False) (C1 ('MetaCons "LeftNeighbor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeftRepeat" 'PrefixI 'False) (U1 :: Type -> Type))

data RightOrnament Source #

Types of single-sided ornaments right of the parent (parent--child).

[p] [ ]
  \
  [c]

Constructors

RightNeighbor

an incomplete right neighbor

RightRepeat

an incomplete right repetition

Instances

Instances details
FromJSON RightOrnament Source # 
Instance details

Defined in PVGrammar

ToJSON RightOrnament Source # 
Instance details

Defined in PVGrammar

Generic RightOrnament Source # 
Instance details

Defined in PVGrammar

Associated Types

type Rep RightOrnament :: Type -> Type #

Show RightOrnament Source # 
Instance details

Defined in PVGrammar

NFData RightOrnament Source # 
Instance details

Defined in PVGrammar

Methods

rnf :: RightOrnament -> () #

Eq RightOrnament Source # 
Instance details

Defined in PVGrammar

Ord RightOrnament Source # 
Instance details

Defined in PVGrammar

type Rep RightOrnament Source # 
Instance details

Defined in PVGrammar

type Rep RightOrnament = D1 ('MetaData "RightOrnament" "PVGrammar" "proto-voice-model-0.1.0.0-IpbUkUcWDicKjQK7SlZCoP" 'False) (C1 ('MetaCons "RightNeighbor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RightRepeat" 'PrefixI 'False) (U1 :: Type -> Type))

Spread

data Spread n Source #

Represents a spread operation. Records for every pitch how it is distributed (see SpreadDirection). The resulting edges (repetitions and passing edges) are represented in a child transition.

Constructors

SpreadOp !(HashMap n SpreadDirection) !(Edges n) 

Instances

Instances details
(Notation n, Eq n, Hashable n) => FromJSON (Spread n) Source # 
Instance details

Defined in PVGrammar

Generic (Spread n) Source # 
Instance details

Defined in PVGrammar

Associated Types

type Rep (Spread n) :: Type -> Type #

Methods

from :: Spread n -> Rep (Spread n) x #

to :: Rep (Spread n) x -> Spread n #

Notation n => Show (Spread n) Source # 
Instance details

Defined in PVGrammar

Methods

showsPrec :: Int -> Spread n -> ShowS #

show :: Spread n -> String #

showList :: [Spread n] -> ShowS #

NFData n => NFData (Spread n) Source # 
Instance details

Defined in PVGrammar

Methods

rnf :: Spread n -> () #

Eq n => Eq (Spread n) Source # 
Instance details

Defined in PVGrammar

Methods

(==) :: Spread n -> Spread n -> Bool #

(/=) :: Spread n -> Spread n -> Bool #

Ord n => Ord (Spread n) Source # 
Instance details

Defined in PVGrammar

Methods

compare :: Spread n -> Spread n -> Ordering #

(<) :: Spread n -> Spread n -> Bool #

(<=) :: Spread n -> Spread n -> Bool #

(>) :: Spread n -> Spread n -> Bool #

(>=) :: Spread n -> Spread n -> Bool #

max :: Spread n -> Spread n -> Spread n #

min :: Spread n -> Spread n -> Spread n #

type Rep (Spread n) Source # 
Instance details

Defined in PVGrammar

type Rep (Spread n) = D1 ('MetaData "Spread" "PVGrammar" "proto-voice-model-0.1.0.0-IpbUkUcWDicKjQK7SlZCoP" 'False) (C1 ('MetaCons "SpreadOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashMap n SpreadDirection)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Edges n))))

data SpreadDirection Source #

Encodes the distribution of a pitch in a spread.

All instances of a pitch must be either moved completely to the left or the right (or both). In addition, some instances may be repeated on the other side. The difference is indicated by the field of the ToLeft and ToRight constructors. For example, ToLeft 3 indicates that out of n instances, all n are moved to the left and n-3 are replicated on the right.

Constructors

ToLeft !Int

all to the left, n fewer to the right

ToRight !Int

all to the right, n fewer to the left

ToBoth

all to both

Instances

Instances details
Monoid SpreadDirection Source # 
Instance details

Defined in PVGrammar

Semigroup SpreadDirection Source # 
Instance details

Defined in PVGrammar

Generic SpreadDirection Source # 
Instance details

Defined in PVGrammar

Associated Types

type Rep SpreadDirection :: Type -> Type #

Show SpreadDirection Source # 
Instance details

Defined in PVGrammar

NFData SpreadDirection Source # 
Instance details

Defined in PVGrammar

Methods

rnf :: SpreadDirection -> () #

Eq SpreadDirection Source # 
Instance details

Defined in PVGrammar

Ord SpreadDirection Source # 
Instance details

Defined in PVGrammar

type Rep SpreadDirection Source # 
Instance details

Defined in PVGrammar

type Rep SpreadDirection = D1 ('MetaData "SpreadDirection" "PVGrammar" "proto-voice-model-0.1.0.0-IpbUkUcWDicKjQK7SlZCoP" 'False) (C1 ('MetaCons "ToLeft" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "ToRight" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "ToBoth" 'PrefixI 'False) (U1 :: Type -> Type)))

Derivations

type PVLeftmost n = Leftmost (Split n) Freeze (Spread n) Source #

Leftmost specialized to the split, freeze, and spread operations of the grammar.

type PVAnalysis n = Analysis (Split n) Freeze (Spread n) (Edges n) (Notes n) Source #

An Analysis specialized to PV types.

analysisTraversePitch :: (Applicative f, Eq n', Hashable n', Ord n') => (n -> f n') -> PVAnalysis n -> f (PVAnalysis n') Source #

Apply an applicative action to all pitches in an analysis.

analysisMapPitch :: (Eq n', Hashable n', Ord n') => (n -> n') -> PVAnalysis n -> PVAnalysis n' Source #

Map a function over all pitches in an analysis.

Loading Files

loadAnalysis :: FilePath -> IO (Either String (PVAnalysis SPitch)) Source #

Loads an analysis from a JSON file (as exported by the annotation tool).

loadAnalysis' :: FilePath -> IO (Either String (PVAnalysis SPC)) Source #

Loads an analysis from a JSON file (as exported by the annotation tool). Converts all pitches to pitch classes.

slicesFromFile :: FilePath -> IO [[(SPitch, RightTied)]] Source #

Loads a MusicXML file and returns a list of salami slices. Each note is expressed as a pitch and a flag that indicates whether the note continues in the next slice.

slicesToPath :: (Interval i, Ord i, Eq i) => [[(Pitch i, RightTied)]] -> Path [Pitch i] [Edge (Pitch i)] Source #

Converts salami slices (as returned by slicesFromFile) to a path as expected by parsers.

loadSurface :: FilePath -> IO (Path [Pitch SInterval] [Edge (Pitch SInterval)]) Source #

Loads a MusicXML File and returns a surface path as input to parsers.

loadSurface' Source #

Arguments

:: FilePath

path to a MusicXML file

-> Int

the first slice to include (starting at 0)

-> Int

the last slice to include

-> IO (Path [Pitch SInterval] [Edge (Pitch SInterval)]) 

Loads a MusicXML File and returns a surface path of the given range of slices.