music-score-1.9.0: Musical score and part representation.

Copyright(c) Hans Hoglund 2012-2014
LicenseBSD-style
Maintainerhans@hanshoglund.se
Stabilityexperimental
Portabilitynon-portable (TF,GNTD)
Safe HaskellNone
LanguageHaskell2010

Music.Score.Export.Backend

Description

 

Synopsis

Documentation

type HasOrdPart a = (HasPart' a, Ord (Part a)) Source

type HasDynamic3 a a' a'' = (HasDynamic' a, HasDynamic' a'', HasDynamic a a', HasDynamic a' a'', HasDynamic a a'') Source

class Functor (BackendScore b) => HasBackend b where Source

This class defines types and functions for exporting music. It provides the primitive types and methods used to implement export.

The backend type b is just a type level tag to identify a specific backend. It is typically defined as an empty data declaration.

The actual conversion is handled by the subclasses HasBackendScore and HasBackendNote, which converts the time structure, and the contained music respectively. Thus structure and content are handled separately.

It is often necessary to alter the events based on their surrounding context: for examples the beginning and end of spanners and beams depend on surrounding notes. The BackendContext type allow HasBackendScore instances to provide context for HasBackendNote instances.

@ data NoteList

instance HasBackend NoteList where type BackendScore NoteList = [] type BackendContext NoteList = Identity type BackendNote NoteList = [(Sum Int, Int)] type BackendMusic NoteList = [(Sum Int, Int)] finalizeExport _ = concat

instance HasBackendScore NoteList [a] a where exportScore _ = fmap Identity

instance HasBackendNote NoteList a => HasBackendNote NoteList [a] where exportNote b ps = mconcat $ map (exportNote b) $ sequenceA ps

instance HasBackendNote NoteList Int where exportNote _ (Identity p) = [(mempty ,p)]

instance HasBackendNote NoteList a => HasBackendNote NoteList (DynamicT (Sum Int) a) where exportNote b (Identity (DynamicT (d,ps))) = set (mapped._1) d $ exportNote b (Identity ps) -- @

Associated Types

type BackendMusic b :: * Source

External music representation

type BackendNote b :: * Source

Notes, chords and rests, with output handled by HasBackendNote

type BackendScore b :: * -> * Source

Score, voice and time structure, with output handled by HasBackendScore

type BackendContext b :: * -> * Source

This type may be used to pass context from exportScore to exportNote. If the note export is not context-sensitive, Identity can be used.

class HasBackend b => HasBackendScore b s where Source

A class for musical container types with an external representation.

The first type parameter is simply a token representing the external format, and the second parameter is the type being represented. In a sense, the first parameter saves us from defining a separate class for each external representation, so rather than having HasMidiScore, HasMusicXmlScore and so on, we have HasBackendScore Midi, HasBackendScore MusicXml and so on.

Associated Types

type BackendScoreEvent b s :: * Source

Type of events in this score type. This is generally just the parameterized type in a container, so we have

  BackendScoreEvent (Score a) ~ a
  BackendScoreEvent (Voice a) ~ a
  

and so on.

It is defined as a type function so that instances can put constraints on the saturated type, rather than being parametric over all note types.

class HasBackend b => HasBackendNote b a where Source

A class for musical event types with an external representation.

The first type parameter is simply a token representing the external format, and the second parameter is the type being represented. In a sense, the first parameter saves us from defining a separate class for each external representation, so rather than having HasMidiNote, HasMusicXmlNote and so on, we have HasBackendNote Midi, HasBackendNote MusicXml and so on.

Minimal complete definition

exportNote

Instances

HasBackendNote Midi Double 
HasBackendNote Midi Float 
HasBackendNote Midi Int 
HasBackendNote Midi Integer 
HasBackendNote NoteList Double 
HasBackendNote NoteList Int 
HasBackendNote SuperCollider Double 
HasBackendNote SuperCollider Int 
HasBackendNote SuperCollider Integer 
HasBackendNote Lilypond Double 
HasBackendNote Lilypond Float 
HasBackendNote Lilypond Int 
HasBackendNote Lilypond Integer 
HasBackendNote MusicXml Double 
HasBackendNote MusicXml Float 
HasBackendNote MusicXml Int 
HasBackendNote MusicXml Integer 
HasBackendNote Midi a => HasBackendNote Midi [a] 
HasBackendNote Midi a => HasBackendNote Midi (Behavior a) 
HasBackendNote Midi a => HasBackendNote Midi (TieT a) 
HasBackendNote Midi a => HasBackendNote Midi (SlideT a) 
HasBackendNote Midi a => HasBackendNote Midi (TextT a) 
HasBackendNote Midi a => HasBackendNote Midi (HarmonicT a) 
HasBackendNote Midi a => HasBackendNote Midi (TremoloT a) 
HasBackendNote Midi a => HasBackendNote Midi (ColorT a) 
HasBackendNote NoteList a => HasBackendNote NoteList [a] 
HasBackendNote NoteList a => HasBackendNote NoteList (TieT a) 
HasBackendNote NoteList a => HasBackendNote NoteList (SlideT a) 
HasBackendNote NoteList a => HasBackendNote NoteList (TextT a) 
HasBackendNote NoteList a => HasBackendNote NoteList (HarmonicT a) 
HasBackendNote NoteList a => HasBackendNote NoteList (TremoloT a) 
HasBackendNote NoteList a => HasBackendNote NoteList (ColorT a) 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider [a] 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider (Behavior a) 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider (TieT a) 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider (SlideT a) 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider (TextT a) 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider (HarmonicT a) 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider (TremoloT a) 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider (ColorT a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond [a] 
Integral a => HasBackendNote Lilypond (Ratio a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (Sum a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (Product a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (Behavior a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (TieT a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (SlideT a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (TextT a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (HarmonicT a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (TremoloT a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (ColorT a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml [a] 
Integral a => HasBackendNote MusicXml (Ratio a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (Sum a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (Product a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (Behavior a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (TieT a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (SlideT a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (TextT a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (HarmonicT a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (TremoloT a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (ColorT a) 
HasBackendNote Midi a => HasBackendNote Midi (PartT n a) 
(Real d, HasBackendNote Midi a) => HasBackendNote Midi (DynamicT d a) 
HasBackendNote Midi a => HasBackendNote Midi (ArticulationT b a) 
HasBackendNote NoteList a => HasBackendNote NoteList (PartT n a) 
HasBackendNote NoteList a => HasBackendNote NoteList (DynamicT b a) 
HasBackendNote NoteList a => HasBackendNote NoteList (ArticulationT b a) 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider (PartT n a) 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider (DynamicT b a) 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider (ArticulationT b a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (PartT n a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (DynamicT DynamicNotation a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (ArticulationT ArticulationNotation a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (PartT n a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (DynamicT DynamicNotation a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (ArticulationT b a) 

export :: (HasBackendScore b s, HasBackendNote b (BackendScoreEvent b s)) => b -> s -> BackendMusic b Source

This is the primitive music export function.

Backend developers are encouraged to provide wrappers on the form toX, writeX etc.