music-score-1.9.0: 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.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 
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) 
IsString a => IsString (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) 
Typeable (* -> *) Behavior 
type Rep Behavior = Time 
type SetPitch b (Behavior a) = b 
type SetDynamic b (Behavior a) = b 
type Diff (Behavior a) = Behavior (Diff a) 
type Scalar (Behavior a) = Behavior (Scalar a) 
type Part (Behavior a) = Behavior (Part a) 
type Pitch (Behavior a) = Behavior a 
type Dynamic (Behavior a) = Behavior a 
type SetPart (Behavior g) (Behavior a) = Behavior (SetPart g a) 

Examples

Construction

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

Common versions

line :: Fractional a => Behavior a Source

A behavior that gives the current time.

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

unit :: Fractional a => Behavior a Source

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

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

turnOn :: Behavior Integer Source

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

turnOff :: Behavior Integer Source

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

sawtooth :: RealFrac a => Behavior a Source

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

sine :: Floating a => Behavior a Source

A behavior that

cosine :: Floating a => Behavior a Source

A behavior that

Combine

switch :: Time -> Behavior a -> Behavior a -> Behavior a Source

Instantly switch from one behavior to another.

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

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

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

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

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

trim   = splice mempty
trim x = trimBefore (x^.onset) . trimAfter (x^.offset)

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

Replace everthing before the given time by mempty.

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

Replace everthing after the given time by mempty.

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

Concatenate a score of (possibly overlapping) segments.

See also concatSegment and continous.

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 Event Segment.

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

Instances

Monad Segment 
Functor 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) 
Typeable (* -> *) Segment 
type Rep Segment = Duration 
type Part (Segment a) = Segment (Part a) 
type SetPart (Segment g) (Segment a) = Segment (SetPart g a) 

Examples

Construction

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

View a segment as a time function and vice versa.

Combine

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) -> Note (Segment a) Source

Append a voice of segments to a single note segment.

Bound type

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 
Eq a => Eq (Bound a) 
Show a => Show (Bound a) 
Semigroup a => Semigroup (Bound a) 
Wrapped (Bound a) 
Transformable a => Transformable (Bound a)

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

(HasPosition a, HasDuration a, Transformable a) => HasDuration (Bound a) 
(HasPosition a, Transformable a) => HasPosition (Bound a) 
Reversible a => Reversible (Bound a) 
Rewrapped (Bound a) (Bound b) 
Typeable (* -> *) Bound 
type Unwrapped (Bound a) = (Span, a) 

Query

bounds :: Time -> Time -> a -> Bound a Source

Add bounds.

bounding :: Span -> a -> Bound a Source

Add bounds.

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

Combine

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

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

trim   = splice mempty
trim x = trimBefore (x^.onset) . trimAfter (x^.offset)

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

Inserts a bounded behavior on top of another behavior.

trim = splice mempty

(Named after the analogous tape-editing technique.)

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

View a Event 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 (Event (Segment a)) (Event (Segment b)) (Bound (Behavior a)) (Bound (Behavior b)) Source

View a Event 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.