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

Portabilitynon-portable (TF,GNTD)
Stabilityexperimental
Maintainerhans@hanshoglund.se
Safe HaskellNone

Music.Time.Score

Contents

Description

 

Synopsis

Score type

data Score a Source

A Score is a sequential or parallel composition of values, and allows overlapping events

You typically create a Score using score, notes, voices, and phrases, or the Alternative interface.

Score is an instance of Transformable, so you can use delay and stretch.

Score is an instance of HasPosition, so you can use duration, onset, offset, era.

To inspect or deconstruct a score, see notes, voices, and phrases, as well as singleNote, singleVoice, and singlePhrase

Instances

Monad Score 
Functor Score 
Typeable1 Score 
MonadPlus Score 
Applicative Score 
Foldable Score 
Traversable Score 
Alternative Score 
FunctorWithIndex Span Score 
FoldableWithIndex Span Score 
TraversableWithIndex Span Score 
HasBackendScore NoteList (Score a) 
(HasPart' a, Ord (Part a), HasMidiProgram (Part a)) => HasBackendScore Midi (Score a) 
(HasPart' a, Ord (Part a)) => HasBackendScore SuperCollider (Score a) 
(HasDynamicNotation a b c, HasArticulationNotation c d e, ~ * (Part e) (Part c), HasOrdPart a, Transformable a, Semigroup a, Tiable e, HasOrdPart c, Show (Part c), HasLilypondInstrument (Part c)) => HasBackendScore Lilypond (Score a) 
(HasDynamicNotation a b c, HasOrdPart a, Transformable a, Semigroup a, HasOrdPart c, Tiable c, Show (Part a), HasMusicXmlInstrument (Part a)) => HasBackendScore MusicXml (Score a) 
Enum a => Enum (Score a) 
Num a => Num (Score a) 
Monoid (Score a) 
Semigroup (Score a) 
Wrapped (Score a) 
VectorSpace (Score a) 
IsDynamics a => IsDynamics (Score a) 
IsPitch a => IsPitch (Score a) 
IsInterval a => IsInterval (Score a) 
Augmentable a => Augmentable (Score a) 
Alterable a => Alterable (Score a) 
AdditiveGroup (Score a) 
Transformable (Score a) 
HasDuration (Score a) 
HasPosition (Score a) 
Splittable a => Splittable (Score a) 
Reversible a => Reversible (Score a) 
HasMeta (Score a) 
Tiable a => Tiable (Score a) 
HasSlide a => HasSlide (Score a) 
HasTremolo a => HasTremolo (Score a) 
HasText a => HasText (Score a) 
HasHarmonic a => HasHarmonic (Score a) 
HasColor a => HasColor (Score a) 
Rewrapped (Score a) (Score b) 
HasParts a b => HasParts (Score a) (Score b) 
HasPitches a b => HasPitches (Score a) (Score b) 
HasDynamics a b => HasDynamics (Score a) (Score b) 
HasArticulations a b => HasArticulations (Score a) (Score b) 
(HasPart' a, Ord (Part a)) => HasPhrases (Score a) (Score b) a b

Traverses all phrases in each voice, using extracted.

Construction

score :: Getter [Note a] (Score a)Source

Create a score from a list of notes.

This is a getter (rather than a function) for consistency:

 [ (0 <-> 1, 10)^.note,
   (1 <-> 2, 20)^.note,
   (3 <-> 4, 30)^.note ]^.score
 view score $ map (view note) [(0 <-> 1, 1)]

Se also notes.

Extracting values

notes :: Lens (Score a) (Score b) [Note a] [Note b]Source

View a Score as a list of Note values.

 view notes                        :: Score a -> [Note a]
 set  notes                        :: [Note a] -> Score a -> Score a
 over notes                        :: ([Note a] -> [Note b]) -> Score a -> Score b
 preview  (notes . each)           :: Score a -> Maybe (Note a)
 preview  (notes . element 1)      :: Score a -> Maybe (Note a)
 preview  (notes . elements odd)   :: Score a -> Maybe (Note a)
 set      (notes . each)           :: Note a -> Score a -> Score a
 set      (notes . element 1)      :: Note a -> Score a -> Score a
 set      (notes . elements odd)   :: Note a -> Score a -> Score a
 over     (notes . each)           :: (Note a -> Note b) -> Score a -> Score b
 over     (notes . element 1)      :: (Note a -> Note a) -> Score a -> Score a
 over     (notes . elements odd)   :: (Note a -> Note a) -> Score a -> Score a
 toListOf (notes . each)                :: Score a -> [Note a]
 toListOf (notes . elements odd)        :: Score a -> [Note a]
 toListOf (notes . each . filtered
              (\x -> _duration x < 2))  :: Score a -> [Note a]

This is not an Iso, as the note list representation does not contain meta-data. To construct a score from a note list, use score or flip (set notes) empty.

events :: Lens (Score a) (Score b) [(Time, Duration, a)] [(Time, Duration, b)]Source

View a score as a list of events, i.e. time-duration-value triplets.

This is a convenient combination of notes and event.

 events = notes . through event event

Pattern matching

singleNote :: Prism' (Score a) (Note a)Source

View a score as a single note.

Unsafe versions

unsafeNotes :: Iso (Score a) (Score b) [Note a] [Note b]Source

View a score as a list of notes.

This only an isomorphism up to meta-data. See also the safe (but more restricted) notes and score.

unsafeEvents :: Iso (Score a) (Score b) [(Time, Duration, a)] [(Time, Duration, b)]Source

View a score as a list of events.

This only an isomorphism up to meta-data. See also the safe (but more restricted) notes and score.

Simultaneous values

simult :: Transformable a => Lens (Score a) (Score b) (Score [a]) (Score [b])Source

simultaneous :: (Transformable a, Semigroup a) => Score a -> Score aSource

Merge all simultaneous events using their Semigroup instance.

Two events a and b are considered simultaneous if and only if they have the same era, that is if era a == era b

Normalize

normalizeScore :: Score a -> Score aSource

Mainly useful for backends.

printEras :: Score a -> IO ()Source

Traversing

mapWithSpan :: (Span -> a -> b) -> Score a -> Score bSource

Map over the values in a score.

filterWithSpan :: (Span -> a -> Bool) -> Score a -> Score aSource

Filter the values in a score.

mapFilterWithSpan :: (Span -> a -> Maybe b) -> Score a -> Score bSource

Combination of mapEvents and filterEvents.

mapEvents :: (Time -> Duration -> a -> b) -> Score a -> Score bSource

Map over the values in a score.

filterEvents :: (Time -> Duration -> a -> Bool) -> Score a -> Score aSource

Filter the values in a score.

mapFilterEvents :: (Time -> Duration -> a -> Maybe b) -> Score a -> Score bSource

Efficient combination of mapEvents and filterEvents.