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

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

Music.Time.Segment

Contents

Description

 

Synopsis

Behavior type

data Behavior a Source

A Behavior is a value varying over time.

Use focusing to view a particular Segment.

Instances

Monad Behavior 
Functor Behavior 
Typeable1 Behavior 
Applicative Behavior 
Distributive Behavior 
Representable Behavior 
HasBackendNote Midi a => HasBackendNote Midi (Behavior a) 
HasBackendNote SuperCollider a => HasBackendNote SuperCollider (Behavior a) 
HasBackendNote Lilypond a => HasBackendNote Lilypond (Behavior a) 
HasBackendNote MusicXml a => HasBackendNote MusicXml (Behavior a) 
Enum a => Enum (Behavior a) 
Eq a => Eq (Behavior a) 
Floating a => Floating (Behavior a) 
Fractional a => Fractional (Behavior a) 
Num a => Num (Behavior a) 
Ord a => Ord (Behavior a) 
Real a => Real (Behavior a) 
Show (Behavior a) 
Monoid a => Monoid (Behavior a) 
Semigroup a => Semigroup (Behavior a) 
VectorSpace a => VectorSpace (Behavior a) 
IsDynamics a => IsDynamics (Behavior a) 
IsPitch a => IsPitch (Behavior a) 
IsInterval a => IsInterval (Behavior a) 
Augmentable a => Augmentable (Behavior a) 
Alterable a => Alterable (Behavior a) 
AffineSpace a => AffineSpace (Behavior a) 
AdditiveGroup a => AdditiveGroup (Behavior a) 
Transformable (Behavior a) 
Reversible (Behavior a) 
Tiable a => Tiable (Behavior a) 
(Transformable a, Transformable b, ~ * b (Pitch b)) => HasPitches (Behavior a) b 
(Transformable a, Transformable b, ~ * b (Pitch b)) => HasPitch (Behavior a) b 
(Transformable a, Transformable b, ~ * b (Dynamic b), ~ * (SetDynamic (Behavior a) b) (Behavior a)) => HasDynamics (Behavior a) b 
(Transformable a, Transformable b, ~ * b (Dynamic b), ~ * (SetDynamic (Behavior a) b) (Behavior a)) => HasDynamic (Behavior a) b 
(HasPart a a, HasPart a b) => HasParts (Behavior a) (Behavior b) 
(HasPart a a, HasPart a b) => HasPart (Behavior a) (Behavior b) 

Examples

behavior :: Iso (Time -> a) (Time -> b) (Behavior a) (Behavior b)Source

View a behavior as a time function and vice versa.

Note that this is just an alias defined to make the documentation nicer:

 behavior = tabulated

Combinators

switch :: Time -> Behavior a -> Behavior a -> Behavior aSource

Instantly switch from one behavior to another.

switch' :: Time -> Behavior a -> Behavior a -> Behavior a -> Behavior aSource

Instantly switch from one behavior to another with an optinal intermediate value.

splice :: Behavior a -> Bound (Behavior a) -> Behavior aSource

Inserts a bounded behavior on top of another behavior.

 trim = splice mempty

(Named after the analogous tape-editing technique.)

trim :: Monoid b => Bound (Behavior b) -> Behavior bSource

Extract a bounded behavior, replacing all values outside the bound with mempty.

 trim   = splice mempty
 trim x = trimBefore _onset x . trimAfter _offset x

trimBefore :: Monoid a => Time -> Behavior a -> Behavior aSource

Replace everthing before the given time by mempty.

trimAfter :: Monoid a => Time -> Behavior a -> Behavior aSource

Replace everthing after the given time by mempty.

concatB :: Monoid a => Score (Behavior a) -> Behavior aSource

Concatenate a score of (possibly overlapping) segments.

See also concatSegment and continous.

Common behaviors

line :: Fractional a => Behavior aSource

A behavior that gives the current time, i.e. the identity function

Should really have the type Behavior Time, but is provided in a more general form for convenience.

unit :: Fractional a => Behavior aSource

A behavior that varies from 0 to 1 during the same time interval and is 0 before and 1 after that interval.

impulse :: Num a => Behavior aSource

A behavior that is 1 at time 0, and 0 at all other times.

turnOn :: Num a => Behavior aSource

A behavior that goes from 0 to 1 at time 0.

turnOff :: Num a => Behavior aSource

A behavior that goes from 1 to 0 at time 0.

sawtooth :: RealFrac a => Behavior aSource

A behavior that goes from 0 to 1 repeatedly with a period of 1.

sine :: Floating a => Behavior aSource

A behavior that

cosine :: Floating a => Behavior aSource

A behavior that

Segment type

data Segment a Source

A Segment is a value varying over some unknown time span. Intuitively, a Segment is to a Behavior what a ray is to a line.

To give a segment an explicit duration, use Stretched Segment.

To place a segment in a particular time span, use Note Segment.

Instances

Monad Segment 
Functor Segment 
Typeable1 Segment 
Applicative Segment 
Distributive Segment 
Representable Segment 
Show (Segment a) 
Transformable (Segment a)

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

Reversible (Segment a) 
(HasPart a a, HasPart a b) => HasParts (Segment a) (Segment b) 
(HasPart a a, HasPart a b) => HasPart (Segment a) (Segment b) 

Examples

segment :: Iso (Duration -> a) (Duration -> b) (Segment a) (Segment b)Source

View a segment as a time function and vice versa.

Combinators

focusing :: Lens' (Behavior a) (Segment a)Source

View part of a Behavior as a Segment.

 line & focusing `onSpan` (2 <-> 3) *~ 0

apSegments :: Voice (Segment a) -> Stretched (Segment a)Source

Append a voice of segments to a single stretched segment.

data Bound a Source

Bound restricts the start and stop time of a value, and prevents access to values outside the bounds.

Bound is especially useful to restrict the range of a Behavior. If we have a value with can only be reasonably defined for a particular time range, we can represent it as Bound Behavior. This is isomorphic to a Note Segment, and bounded whitnesses the isomorphism.

Bound is not Foldable or Traversable, as that would allow us to access values outside the bounds. However, we can still access values of a Bound Behavior in a safe manner using trim or splice.

Instances

Functor Bound 
Typeable1 Bound 
Eq a => Eq (Bound a) 
Show a => Show (Bound a) 
Semigroup a => Semigroup (Bound a) 
Wrapped (Bound a)

Unsafe: Do not use Wrapped instances

Transformable a => Transformable (Bound a)

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

(HasPosition a, HasDuration a) => HasDuration (Bound a) 
HasPosition a => HasPosition (Bound a) 
(HasPosition a, Splittable a) => Splittable (Bound a) 
Reversible a => Reversible (Bound a) 
Rewrapped (Bound a) (Bound b) 

bounds :: Time -> Time -> a -> Bound aSource

Add bounds.

bounding :: Span -> a -> Bound aSource

Add bounds.

 (s,x)^.note = (bounding s . transform s) x

trim :: Monoid b => Bound (Behavior b) -> Behavior bSource

Extract a bounded behavior, replacing all values outside the bound with mempty.

 trim   = splice mempty
 trim x = trimBefore _onset x . trimAfter _offset x

splice :: Behavior a -> Bound (Behavior a) -> Behavior aSource

Inserts a bounded behavior on top of another behavior.

 trim = splice mempty

(Named after the analogous tape-editing technique.)

bounded' :: Iso' (Note (Segment a)) (Bound (Behavior a))Source

View a Note Segment as a Bound Behavior and vice versa.

This can be used to safely turn a behavior into a segment and vice versa. Often focusing is more convenient to use.

bounded :: Iso (Note (Segment a)) (Note (Segment b)) (Bound (Behavior a)) (Bound (Behavior b))Source

View a Note Segment as a Bound Behavior and vice versa.

This can be used to safely turn a behavior into a segment and vice versa. Often focusing is more convenient to use.