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

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

Music.Score.Combinators

Contents

Description

Combinators for manipulating scores.

Synopsis

Preliminaries

type Monoid' a = (Monoid a, Semigroup a)Source

This pseudo-class can be used in place of Monoid whenever an additional Semigroup constraint is needed.

Ideally, Monoid should be changed to extend Semigroup instead.

class (Stretchable s, Delayable s, AdditiveGroup (Time s), AffineSpace (Time s)) => Transformable1 s Source

This class includes time-based structures that can be scaled and moved in time.

class (HasOnset s, HasOffset s, Transformable1 s) => Transformable s Source

This class includes time-based structures with a known position in time.

Instances

class (MonadPlus s, Transformable s) => Composable s Source

This class includes time-based structures that can be transcribed.

Instances

class (Performable s, Composable s) => HasEvents s Source

This class includes time-based structures that can be perfomed and transcribed.

The combined power of perform and compose give us the power to traverse and the entire event structure, as per mapEvents.

Instances

Composing scores

(|>) :: (Semigroup (s a), AffineSpace (Time s), HasOnset s, HasOffset s, Delayable s) => s a -> s a -> s aSource

Compose in sequence.

To compose in parallel, use <>.

 Score a -> Score a -> Score a

(<|) :: (Semigroup (s a), AffineSpace (Time s), HasOnset s, HasOffset s, Delayable s) => s a -> s a -> s aSource

Compose in reverse sequence.

To compose in parallel, use <>.

 Score a -> Score a -> Score a

scat :: (Monoid' (s a), AffineSpace (Time s), HasOnset s, HasOffset s, Delayable s) => [s a] -> s aSource

Sequential concatentation.

 [Score t] -> Score t

pcat :: Monoid a => [a] -> aSource

Parallel concatentation. A synonym for mconcat.

 [Score t] -> Score t

Special composition

sustain :: (Fractional (Duration s), Semigroup (s a), Stretchable s, HasDuration s) => s a -> s a -> s aSource

Like <>, but scaling the second agument to the duration of the first.

 Score a -> Score a -> Score a

anticipate :: (Semigroup (s a), Transformable s, d ~ Duration s, Ord d) => d -> s a -> s a -> s aSource

Like |> but with a negative delay on the second element.

 Duration -> Score a -> Score a -> Score a

Transforming scores

Moving in time

move :: (Delayable s, d ~ Duration s) => d -> s a -> s aSource

Move a score forward in time. Equivalent to delay.

 Duration -> Score a -> Score a

moveBack :: (Delayable s, AdditiveGroup d, d ~ Duration s) => d -> s a -> s aSource

Move a score backward in time. Negated verison of delay

 Duration -> Score a -> Score a

startAt :: (HasOnset s, Delayable s, AffineSpace t, t ~ Time s) => t -> s a -> s aSource

Move a score so that its onset is at the specific time.

 Duration -> Score a -> Score a

stopAt :: (HasOffset s, Delayable s, AffineSpace t, t ~ Time s) => t -> s a -> s aSource

Move a score so that its offset is at the specific time.

 Duration -> Score a -> Score a

Stretching in time

stretch :: Stretchable s => Duration s -> s a -> s aSource

Stretch (augment) a value by the given factor.

 Duration -> Score a -> Score a

compress :: (Stretchable s, Fractional d, d ~ Duration s) => d -> s a -> s aSource

Compress (diminish) a score. Flipped version of ^/.

 Duration -> Score a -> Score a

stretchTo :: (Stretchable s, HasDuration s, Fractional d, d ~ Duration s) => d -> s a -> s aSource

Stretch a score to fit into the given duration.

 Duration -> Score a -> Score a

Rests

rest :: MonadPlus s => s (Maybe a)Source

Create a score containing a rest at time zero of duration one.

This function uses the unit position (0, 1).

 Score (Maybe a)

removeRests :: MonadPlus m => m (Maybe a) -> m aSource

Remove rests from a score.

This is just an alias for mcatMaybes which reads better in certain contexts.

 Score (Maybe a) -> Score a

Repetition

times :: (Monoid' (s a), Transformable s) => Int -> s a -> s aSource

Repeat exact amount of times.

 Duration -> Score Note -> Score Note

repeated :: (Monoid' (s b), Transformable s) => [a] -> (a -> s b) -> s bSource

Repeat once for each element in the list.

Example:

 repeated [1,2,1] (c^*)

Simple type:

 [a] -> (a -> Score Note) -> Score Note

group :: (Monoid' (s a), Transformable s, Time s ~ TimeT) => Int -> s a -> s aSource

Repeat a number of times and scale down by the same amount.

 Duration -> Score a -> Score a

Transformations

perform :: (Performable s, t ~ Time s, d ~ Duration s) => s a -> [(t, d, a)]Source

Perform a score.

This is the inverse of compose

compose :: (Composable s, d ~ Duration s, t ~ Time s) => [(t, d, a)] -> s aSource

Recompose a score.

This is the inverse of perform

 [(Time, Duration, a)] -> Score a

retrograde :: (HasEvents s, t ~ Time s, Num t, Ord t) => s a -> s aSource

Reverse a score around its middle point (TODO not correct documentation w.r.t to start).

 onset a    = onset (retrograde a)
 duration a = duration (retrograde a)
 offset a   = offset (retrograde a)
 Score a -> Score a

mapEvents :: (HasPart' a, HasEvents s, t ~ Time s, d ~ Duration s) => (t -> d -> a -> b) -> s a -> s bSource

Map over the events in a score.

 (Time -> Duration -> a -> b) -> Score a -> Score b

filterEvents :: (HasPart' a, HasEvents s, t ~ Time s, d ~ Duration s) => (t -> d -> a -> Bool) -> s a -> s aSource

Map over the events in a score.

 (Time -> Duration -> a -> b) -> Score a -> Score b

mapFilterEvents :: (HasPart' a, HasEvents s, t ~ Time s, d ~ Duration s) => (t -> d -> a -> Maybe b) -> s a -> s bSource

Map over the events in a score.

 (Time -> Duration -> a -> b) -> Score a -> Score b

mapAllEvents :: (HasEvents s, d ~ Duration s, t ~ Time s) => ([(t, d, a)] -> [(t, d, b)]) -> s a -> s bSource

mapEventsSingle :: (HasEvents s, t ~ Time s, d ~ Duration s) => (t -> d -> a -> b) -> s a -> s bSource

Equivalent to mapEvents for single-voice scores. Fails if the score contains overlapping events.

 (Time -> Duration -> a -> b) -> Score a -> Score b

mapFirst :: (HasPart' a, HasEvents s) => (a -> b) -> (a -> b) -> s a -> s bSource

Map over the first, and remaining notes in each part.

If a part has only one notes, the first function is applied. If a part has no notes, the given score is returned unchanged.

 (a -> b) -> (a -> b) -> Score a -> Score b

mapLast :: (HasPart' a, HasEvents s) => (a -> b) -> (a -> b) -> s a -> s bSource

Map over the last, and preceding notes in each part.

If a part has only one notes, the first function is applied. If a part has no notes, the given score is returned unchanged.

 (a -> b) -> (a -> b) -> Score a -> Score b

mapPhrase :: (HasPart' a, HasEvents s) => (a -> b) -> (a -> b) -> (a -> b) -> s a -> s bSource

Map over the first, middle and last note in each part.

If a part has fewer than three notes the first takes precedence over the last, and last takes precedence over the middle.

 (a -> b) -> (a -> b) -> (a -> b) -> Score a -> Score b

mapPhraseSingle :: HasEvents s => (a -> b) -> (a -> b) -> (a -> b) -> s a -> s bSource

Equivalent to mapPhrase for single-voice scores. Fails if the score contains overlapping events.

 (a -> b) -> (a -> b) -> (a -> b) -> Score a -> Score b

Conversion

scoreToVoice :: Score a -> Voice (Maybe a)Source

Convert a score into a voice.

This function fails if the score contain overlapping events.

voiceToScore :: Voice a -> Score aSource

Convert a voice into a score.

voiceToScore' :: Voice (Maybe a) -> Score aSource

Convert a voice which may contain rests into a score.

eventToScore :: (Monad s, Transformable1 s, Time s ~ t, Duration s ~ d) => (t, d, a) -> s aSource