music-score-1.7.2: 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.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

Alternative Score 
Monad Score 
Functor Score 
MonadPlus Score 
Applicative Score 
Foldable Score 
Traversable Score 
(HasPart' a, Ord (Part a), HasMidiProgram (Part a)) => HasBackendScore Midi (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), Satisfied) => HasBackendScore Lilypond (Score a) 
HasBackendScore NoteList (Score a) 
(HasPart' a, Ord (Part a)) => HasBackendScore SuperCollider (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) 
(Show a, Transformable a) => Show (Score a) 
IsString a => IsString (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) 
HasText a => HasText (Score a) 
HasHarmonic a => HasHarmonic (Score a) 
HasTremolo a => HasTremolo (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.

Typeable (* -> *) Score 
type SetPart g (Score a) = Score (SetPart g a) 
type SetPitch b (Score a) = Score (SetPitch b a) 
type SetDynamic b (Score a) = Score (SetDynamic b a) 
type SetArticulation b (Score a) = Score (SetArticulation b a) 
type BackendScoreEvent Midi (Score a) = a 
type BackendScoreEvent Lilypond (Score a) = SetArticulation ArticulationNotation (SetDynamic DynamicNotation a) 
type BackendScoreEvent NoteList (Score a) = a 
type BackendScoreEvent SuperCollider (Score a) = a 
type BackendScoreEvent MusicXml (Score a) = SetDynamic DynamicNotation a 
type Unwrapped (Score a) 
type Scalar (Score a) = Duration 
type Part (Score a) = Part a 
type Pitch (Score a) = Pitch a 
type Dynamic (Score a) = Dynamic a 
type Articulation (Score a) = Articulation a 

Query

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.

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.

eras :: Traversal' (Score a) Span Source

Print all eras of the given score.

>>> toListOf eras $ scat [c,d,e :: Score Integer]
[0 <-> 1,1 <-> 2,2 <-> 3]

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

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

Deprecated: Use 'unsafeNotes . single'

View a score as a single note.

Traversal

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

Map over the values in a score.

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

Filter the values in a score.

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

Combination of mapEvents and filterEvents.

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

Map over the values in a score.

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

Filter the values in a score.

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

Efficient combination of mapEvents and filterEvents.

Simultaneous

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

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

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 a Source

Mainly useful for backends.

printEras :: Score a -> IO () Source

Extract all eras of the given score.

>>> printEras $ scat [c,d,e :: Score Integer]
0 <-> 1
1 <-> 2
2 <-> 3

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.