| Maintainer | byorgey@cis.upenn.edu | 
|---|---|
| Safe Haskell | None | 
Data.Active
Contents
Description
Inspired by the work of Kevin Matlage and Andy Gill (Every
 Animation Should Have a Beginning, a Middle, and an End, Trends
 in Functional Programming,
 2010. http://ittc.ku.edu/csdl/fpg/node/46), this module defines a
 simple abstraction for working with time-varying values.  A value
 of type Active a is either a constant value of type a, or a
 time-varying value of type a (i.e. a function from time to
 a) with specific start and end times.  Since active values
 have start and end times, they can be aligned, sequenced,
 stretched, or reversed.
In a sense, this is sort of like a stripped-down version of functional reactive programming (FRP), without the reactivity.
The original motivating use for this library is to support making animations with the diagrams framework (http://projects.haskell.org/diagrams), but the hope is that it may find more general utility.
There are two basic ways to create an Active value.  The first is
 to use mkActive to create one directly, by specifying a start and
 end time and a function of time.  More indirectly, one can use the
 Applicative instance together with the unit interval ui, which
 takes on values from the unit interval from time 0 to time 1, or
 interval, which creates an active over an arbitrary interval.
For example, to create a value of type Active Double which
 represents one period of a sine wave starting at time 0 and ending
 at time 1, we could write
mkActive 0 1 (\t -> sin (fromTime t * tau))
or
(sin . (*tau)) <$> ui
pure can also be used to create Active values which are
 constant and have no start or end time.  For example,
mod <$> (floor <$> interval 0 100) <*> pure 7
cycles repeatedly through the numbers 0-6.
Note that the "idiom bracket" notation supported by the SHE
 preprocessor (http://personal.cis.strath.ac.uk/~conor/pub/she/,
 http://hackage.haskell.org/package/she) can make for somewhat
 more readable Applicative code.  For example, the above example
 can be rewritten using SHE as
 {-# OPTIONS_GHC -F -pgmF she #-}
 ... (| mod (| floor (interval 0 100) |) ~7 |)
There are many functions for transforming and composing active values; see the documentation below for more details.
- data Time
- toTime :: Real a => a -> Time
- fromTime :: Fractional a => Time -> a
- data Duration
- toDuration :: Real a => a -> Duration
- fromDuration :: Fractional a => Duration -> a
- data Era
- mkEra :: Time -> Time -> Era
- start :: Era -> Time
- end :: Era -> Time
- duration :: Era -> Duration
- data  Dynamic a = Dynamic {- era :: Era
- runDynamic :: Time -> a
 
- mkDynamic :: Time -> Time -> (Time -> a) -> Dynamic a
- onDynamic :: (Time -> Time -> (Time -> a) -> b) -> Dynamic a -> b
- shiftDynamic :: Duration -> Dynamic a -> Dynamic a
- data Active a
- mkActive :: Time -> Time -> (Time -> a) -> Active a
- fromDynamic :: Dynamic a -> Active a
- isConstant :: Active a -> Bool
- isDynamic :: Active a -> Bool
- onActive :: (a -> b) -> (Dynamic a -> b) -> Active a -> b
- modActive :: (a -> b) -> (Dynamic a -> Dynamic b) -> Active a -> Active b
- runActive :: Active a -> Time -> a
- activeEra :: Active a -> Maybe Era
- setEra :: Era -> Active a -> Active a
- atTime :: Time -> Active a -> Active a
- activeStart :: Active a -> a
- activeEnd :: Active a -> a
- ui :: Fractional a => Active a
- interval :: Fractional a => Time -> Time -> Active a
- stretch :: Rational -> Active a -> Active a
- stretchTo :: Duration -> Active a -> Active a
- during :: Active a -> Active a -> Active a
- shift :: Duration -> Active a -> Active a
- backwards :: Active a -> Active a
- snapshot :: Time -> Active a -> Active a
- clamp :: Active a -> Active a
- clampBefore :: Active a -> Active a
- clampAfter :: Active a -> Active a
- trim :: Monoid a => Active a -> Active a
- trimBefore :: Monoid a => Active a -> Active a
- trimAfter :: Monoid a => Active a -> Active a
- after :: Active a -> Active a -> Active a
- (->>) :: Semigroup a => Active a -> Active a -> Active a
- (|>>) :: Active a -> Active a -> Active a
- movie :: [Active a] -> Active a
- discrete :: [a] -> Active a
- simulate :: Rational -> Active a -> [a]
Representing time
Time and duration
An abstract type for representing points in time.  Note that
   literal numeric values may be used as Times, thanks to the the
   Num and Fractional instances.  toTime and fromTime are
   also provided for convenience in converting between Time and
   other numeric types.
fromTime :: Fractional a => Time -> aSource
Convert a Time to a value of any Fractional type (such as
   Rational, Float, or Double).
An abstract type representing elapsed time between two points
   in time.  Note that durations can be negative. Literal numeric
   values may be used as Durations thanks to the Num and
   Fractional instances. toDuration and fromDuration are also
   provided for convenience in converting between Durations and
   other numeric types.
toDuration :: Real a => a -> DurationSource
fromDuration :: Fractional a => Duration -> aSource
Convert a Duration to any other Fractional type (such as
   Rational, Float, or Double).
Eras
An Era is a concrete span of time, that is, a pair of times
   representing the start and end of the era. Eras form a
   semigroup: the combination of two Eras is the smallest Era
   which contains both.  They do not form a Monoid, since there is
   no Era which acts as the identity with respect to this
   combining operation.
Era is abstract. To construct Era values, use mkEra; to
   deconstruct, use start and end.
Dynamic values
A Dynamic a can be thought of as an a value that changes over
   the course of a particular Era.  It's envisioned that Dynamic
   will be mostly an internal implementation detail and that
   Active will be most commonly used.  But you never know what
   uses people might find for things.
Constructors
| Dynamic | |
| Fields 
 | |
Instances
| Functor Dynamic | |
| Apply Dynamic | 
 | 
| Semigroup a => Semigroup (Dynamic a) | 
 | 
| Newtype (Active a) (MaybeApply Dynamic a) | 
mkDynamic :: Time -> Time -> (Time -> a) -> Dynamic aSource
Create a Dynamic from a start time, an end time, and a
   time-varying value.
shiftDynamic :: Duration -> Dynamic a -> Dynamic aSource
Shift a Dynamic value by a certain duration.
Active values
For working with time-varying values, it is convenient to have an
 Applicative instance: <*> lets us apply time-varying
 functions to time-varying values; pure allows treating constants
 as time-varying values which do not vary.  However, as explained in
 its documentation, Dynamic cannot be made an instance of
 Applicative since there is no way to implement pure.  The
 problem is that all Dynamic values must have a finite start and
 end time.  The solution is to adjoin a special constructor for
 pure/constant values with no start or end time, giving us Active.
There are two types of Active values:
-  An Activecan simply be aDynamic, that is, a time-varying value with start and end times.
-  An Activevalue can also be a constant: a single value, constant across time, with no start and end times.
The addition of constant values enable Monoid and Applicative
   instances for Active.
Instances
| Functor Active | |
| Applicative Active | |
| Apply Active | |
| (Monoid a, Semigroup a) => Monoid (Active a) | |
| Semigroup a => Semigroup (Active a) | Active values over a type with a  | 
| Newtype (Active a) (MaybeApply Dynamic a) | 
mkActive :: Time -> Time -> (Time -> a) -> Active aSource
Create a dynamic Active from a start time, an end time, and a
   time-varying value.
isConstant :: Active a -> BoolSource
Test whether an Active value is constant.
modActive :: (a -> b) -> (Dynamic a -> Dynamic b) -> Active a -> Active bSource
Modify an Active value using a case analysis to see whether it
   is constant or dynamic.
atTime :: Time -> Active a -> Active aSource
atTime t a is an active value with the same behavior as a,
   shifted so that it starts at time t.  If a is constant it is
   returned unchanged.
activeStart :: Active a -> aSource
Get the value of an Active a at the beginning of its era.
Combinators
Special active values
ui :: Fractional a => Active aSource
ui represents the unit interval, which takes on the value t
   at time t, and has as its era [0,1]. It is equivalent to
   interval 0 1
 
On the x-axis is time, and the value that ui takes on is on the
   y-axis.  The shaded portion represents the era.  Note that the
   value of ui (as with any active) is still defined outside its
   era, and this can make a difference when it is combined with
   other active values with different eras.  Applying a function
   with fmap affects all values, both inside and outside the era.
   To manipulate values outside the era specifically, see clamp
   and trim.
To alter the values that ui takes on without altering its
   era, use its Functor and Applicative instances.  For example,
   (*2) <$> ui varies from 0 to 2 over the era [0,1].  To
   alter the era, you can use stretch or shift.
interval :: Fractional a => Time -> Time -> Active aSource
interval a b is an active value starting at time a, ending at
   time b, and taking the value t at time t.
Transforming active values
stretch :: Rational -> Active a -> Active aSource
stretch s act "stretches" the active act so that it takes
   s times as long (retaining the same start time).
shift :: Duration -> Active a -> Active aSource
shift d act shifts the start time of act by duration d.
   Has no effect on constant values.
backwards :: Active a -> Active aSource
Reverse an active value so the start of its era gets mapped to
   the end and vice versa.  For example, backwards  can be
   visualized as
ui
 
snapshot :: Time -> Active a -> Active aSource
Take a "snapshot" of an active value at a particular time, resulting in a constant value.
Working with values outside the era
clamp :: Active a -> Active aSource
"Clamp" an active value so that it is constant before and after
   its era.  Before the era, clamp a takes on the value of a at
   the start of the era.  Likewise, after the era, clamp a takes
   on the value of a at the end of the era. clamp has no effect
   on constant values.
For example, clamp  can be visualized as
ui
 
See also clampBefore and clampAfter, which clamp only before
   or after the era, respectively.
clampBefore :: Active a -> Active aSource
clampAfter :: Active a -> Active aSource
trim :: Monoid a => Active a -> Active aSource
"Trim" an active value so that it is empty outside its era.
   trim has no effect on constant values.
For example, trim  can be visualized as
ui
 
Actually, trim ui is not well-typed, since it is not guaranteed
   that ui's values will be monoidal (and usually they won't be)!
   But the above image still provides a good intuitive idea of what
   trim is doing. To make this precise we could consider something
   like trim (First . Just $ ui).
See also trimBefore and trimActive, which trim only before or
   after the era, respectively.
trimBefore :: Monoid a => Active a -> Active aSource
Composing active values
after :: Active a -> Active a -> Active aSource
a1 `after` a2 produces an active that behaves like a1 but is
   shifted to start at the end time of a2.  If either a1 or a2
   are constant, a1 is returned unchanged.
movie :: [Active a] -> Active aSource
Splice together a list of active values using |>>.  The list
   must be nonempty.
Discretization
discrete :: [a] -> Active aSource
Create an Active which takes on each value in the given list in
   turn during the time [0,1], with each value getting an equal
   amount of time.  In other words, discrete creates a "slide
   show" that starts at time 0 and ends at time 1.  The first
   element is used prior to time 0, and the last element is used
   after time 1.
It is an error to call discrete on the empty list.
simulate :: Rational -> Active a -> [a]Source
simulate r act simulates the Active value act, returning a
   list of "snapshots" taken at regular intervals from the start
   time to the end time.  The interval used is determined by the
   rate r, which denotes the "frame rate", that is, the number
   of snapshots per unit time.
If the Active value is constant (and thus has no start or end
   times), a list of length 1 is returned, containing the constant
   value.
 
 
 
