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

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

Music.Time.Internal.Transform

Contents

Description

 

Synopsis

The Transformable class

class Transformable a whereSource

Class of values that can be transformed (i.e. scaled and moved) in time.

Law

 transform mempty = id
 transform (s <> t) = transform s . transform t
 transform (s <> negateV s) = id

Law

 onset (delay n a)       = n ^+. onset a
 offset (delay n a)      = n ^+. offset a
 duration (stretch n a)  = n * duration a
 duration (compress n a) = duration a / n
 delay n b ! t    = b ! (t .-^ n)
 undelay n b ! t  = b ! (t .+^ n)

Lemma

 duration a = duration (delay n a)

Methods

transform :: Span -> a -> aSource

Instances

Transformable Bool 
Transformable Char 
Transformable Double 
Transformable Float 
Transformable Int 
Transformable Integer 
Transformable Ordering 
Transformable () 
Transformable Span 
Transformable Time 
Transformable Duration 
Transformable Meta 
Transformable Attribute 
Transformable DynamicNotation 
Transformable ArticulationNotation 
Transformable a => Transformable [a] 
Transformable a => Transformable (Ratio a) 
Transformable a => Transformable (Maybe a) 
Transformable a => Transformable (Sum a) 
Transformable a => Transformable (Product a) 
Transformable a => Transformable (Seq a) 
Transformable a => Transformable (Last a) 
Transformable a => Transformable (Option a) 
Transformable (NoReverse a) 
Transformable a => Transformable (Bound a)

Bound transform by transforming the bounded value as well as the bounds.

Transformable a => Transformable (Average a) 
Transformable a => Transformable (Ctxt a) 
Transformable a => Transformable (AddMeta a) 
Transformable (Stretched a) 
Transformable (Voice a) 
Transformable (Delayed a) 
Transformable (Chord a) 
Transformable (Track a) 
Transformable (Note a) 
Transformable (Score a) 
Transformable (Behavior a) 
Transformable (Segment a)

Segments are invariant under transformation. To transform a timve varying value, use fromSegment.

Transformable (Reactive a) 
Transformable a => Transformable (TieT a) 
Transformable a => Transformable (SlideT a) 
Transformable a => Transformable (TremoloT a) 
Transformable a => Transformable (TextT a) 
Transformable a => Transformable (HarmonicT a) 
Transformable a => Transformable (ColorT a) 
(Transformable a, Transformable b) => Transformable (a -> b)

Functions transform by conjugation, i.e. we reverse-transform the argument and transform the result.

Transformable a => Transformable (b, a) 
(Ord k, Transformable a) => Transformable (Map k a) 
(Monoid b, Transformable a) => Transformable (Couple b a) 
Transformable a => Transformable (PartT n a) 
Transformable a => Transformable (DynamicT n a) 
Transformable a => Transformable (ArticulationT n a) 
(Transformable a, Transformable b, Transformable c) => Transformable (a, b, c) 

itransform :: Transformable a => Span -> a -> aSource

Apply the inverse of the given transformation.

 itransform s = transform (negateV s)

transformed :: Transformable a => Span -> Iso' a aSource

View the given value in the context of the given transformation.

 over (transformed s) = (`whilst` s)

Apply under a transformation

whilst :: (Transformable a, Transformable b) => (a -> b) -> Span -> a -> bSource

Apply a function under transformation.

Designed to be used infix, as in

 stretch 2 `whilst` delaying 2

whilstM :: (Functor f, Transformable a, Transformable b) => (a -> f b) -> Span -> a -> f bSource

Apply a morphism under transformation (monadic version).

whilstL :: (Functor f, Transformable a, Transformable b) => LensLike f s t a b -> LensLike f (Span, s) (Span, t) a bSource

whilstLT :: (Functor f, Transformable a, Transformable b) => LensLike f s t a b -> LensLike f (Time, s) (Time, t) a bSource

whilstStretch :: (Transformable a, Transformable b) => (a -> b) -> Duration -> a -> bSource

Apply a function under transformation.

whilstDelay :: (Transformable a, Transformable b) => (a -> b) -> Time -> a -> bSource

Apply a function under transformation.

spanned :: (Transformable a, Transformable b) => Span -> Lens a b a bSource

Transforms a lens of to a Transformable type to act inside a transformation.

onSpan :: (Transformable a, Functor f) => LensLike' f a b -> Span -> LensLike' f a bSource

Transforms a lens of to a Transformable type to act inside a transformation.

Designed to be used infix, as in

 l `onSpan` (2 <-> 3)

conjugateS :: Span -> Span -> SpanSource

The conjugate of two spans.

Specific transformations

delay :: Transformable a => Duration -> a -> aSource

Moves a value forward in time.

undelay :: Transformable a => Duration -> a -> aSource

Moves a value backward in time. Equnitvalent to stretch . negate.

stretch :: Transformable a => Duration -> a -> aSource

Stretches (augments) a value by the given factor.

compress :: Transformable a => Duration -> a -> aSource

Compresses (diminishes) a score. Equnitvalent to stretch . recip.

Applied transformations

delaying :: Duration -> SpanSource

A transformation that moves a value forward in time.

undelaying :: Duration -> SpanSource

A transformation that moves a value backward in time.

stretching :: Duration -> SpanSource

A transformation that stretches (augments) a value by the given factor.

compressing :: Duration -> SpanSource

A transformation that compresses (diminishes) a value by the given factor.

Utility

delayTime :: Transformable a => Time -> a -> aSource

Delay relative to origin.

Provided for situations when we really want to use startAt, but the type does not have an instance for HasPosition and we can assume that the value is starting at time zero.