| Copyright | (c) Hans Hoglund 2012-2014 |
|---|---|
| License | BSD-style |
| Maintainer | hans@hanshoglund.se |
| Stability | experimental |
| Portability | non-portable (TF,GNTD) |
| Safe Haskell | None |
| Language | Haskell2010 |
Music.Time.Segment
Contents
Description
- data Behavior a
- behavior :: Iso (Time -> a) (Time -> b) (Behavior a) (Behavior b)
- line :: Fractional a => Behavior a
- unit :: Fractional a => Behavior a
- impulse :: Num a => Behavior a
- turnOn :: Behavior Integer
- turnOff :: Behavior Integer
- sawtooth :: RealFrac a => Behavior a
- sine :: Floating a => Behavior a
- cosine :: Floating a => Behavior a
- switch :: Time -> Behavior a -> Behavior a -> Behavior a
- switch' :: Time -> Behavior a -> Behavior a -> Behavior a -> Behavior a
- splice :: Behavior a -> Bound (Behavior a) -> Behavior a
- trim :: Monoid b => Bound (Behavior b) -> Behavior b
- trimBefore :: Monoid a => Time -> Behavior a -> Behavior a
- trimAfter :: Monoid a => Time -> Behavior a -> Behavior a
- concatB :: Monoid a => Score (Behavior a) -> Behavior a
- data Segment a
- segment :: Iso (Duration -> a) (Duration -> b) (Segment a) (Segment b)
- focusing :: Lens' (Behavior a) (Segment a)
- apSegments' :: Note (Segment a) -> Note (Segment a) -> Note (Segment a)
- apSegments :: Voice (Segment a) -> Note (Segment a)
- data Bound a
- bounds :: Time -> Time -> a -> Bound a
- bounding :: Span -> a -> Bound a
- trim :: Monoid b => Bound (Behavior b) -> Behavior b
- splice :: Behavior a -> Bound (Behavior a) -> Behavior a
- bounded' :: Iso' (Event (Segment a)) (Bound (Behavior a))
- bounded :: Iso (Event (Segment a)) (Event (Segment b)) (Bound (Behavior a)) (Bound (Behavior b))
Behavior type
A Behavior is a value varying over time.
Use focusing to view a particular Segment.
Instances
Examples
Construction
Common versions
line :: Fractional a => Behavior a Source
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.
sawtooth :: RealFrac a => Behavior a Source
A behavior that goes from 0 to 1 repeatedly with a period of 1.
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.
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
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
|
| 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
apSegments :: Voice (Segment a) -> Note (Segment a) Source
Append a voice of segments to a single note segment.
Bound type
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) |
|
| (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) |