active-0.1.0.19: Abstractions for animation

Copyright(c) 2011 Brent Yorgey
LicenseBSD-style (see LICENSE)
Maintainerbyorgey@cis.upenn.edu
Safe HaskellNone
LanguageHaskell2010

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.

Synopsis

Representing time

Time and duration

data Time Source

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.

toTime :: Real a => a -> Time Source

Convert any value of a Real type (including Int, Integer, Rational, Float, and Double) to a Time.

fromTime :: Fractional a => Time -> a Source

Convert a Time to a value of any Fractional type (such as Rational, Float, or Double).

data Duration Source

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

Convert any value of a Real type (including Int, Integer, Rational, Float, and Double) to a Duration.

fromDuration :: Fractional a => Duration -> a Source

Convert a Duration to any other Fractional type (such as Rational, Float, or Double).

Eras

data Era Source

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.

Instances

mkEra :: Time -> Time -> Era Source

Create an Era by specifying start and end Times.

start :: Era -> Time Source

Get the start Time of an Era.

end :: Era -> Time Source

Get the end Time of an Era.

duration :: Era -> Duration Source

Compute the Duration of an Era.

Dynamic values

data Dynamic a Source

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

era :: Era
 
runDynamic :: Time -> a
 

Instances

Functor Dynamic 
Apply Dynamic

Dynamic is an instance of Apply (i.e. Applicative without pure): a time-varying function is applied to a time-varying value pointwise; the era of the result is the combination of the function and value eras. Note, however, that Dynamic is not an instance of Applicative since there is no way to implement pure: the era would have to be empty, but there is no such thing as an empty era (that is, Era is not an instance of Monoid).

Semigroup a => Semigroup (Dynamic a)

Dynamic a is a Semigroup whenever a is: the eras are combined according to their semigroup structure, and the values of type a are combined pointwise. Note that Dynamic a cannot be an instance of Monoid since Era is not.

Newtype (Active a) (MaybeApply Dynamic a) 

mkDynamic :: Time -> Time -> (Time -> a) -> Dynamic a Source

Create a Dynamic from a start time, an end time, and a time-varying value.

onDynamic :: (Time -> Time -> (Time -> a) -> b) -> Dynamic a -> b Source

Fold for Dynamic.

shiftDynamic :: Duration -> Dynamic a -> Dynamic a Source

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.

data Active a Source

There are two types of Active values:

  • An Active can simply be a Dynamic, that is, a time-varying value with start and end times.
  • An Active value 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 Semigroup instance are also an instance of Semigroup. Two active values are combined pointwise; the resulting value is constant iff both inputs are.

Newtype (Active a) (MaybeApply Dynamic a) 

mkActive :: Time -> Time -> (Time -> a) -> Active a Source

Create a dynamic Active from a start time, an end time, and a time-varying value.

fromDynamic :: Dynamic a -> Active a Source

Create an Active value from a Dynamic.

isConstant :: Active a -> Bool Source

Test whether an Active value is constant.

isDynamic :: Active a -> Bool Source

Test whether an Active value is Dynamic.

onActive :: (a -> b) -> (Dynamic a -> b) -> Active a -> b Source

Fold for Actives. Process an 'Active a', given a function to apply if it is a pure (constant) value, and a function to apply if it is a Dynamic.

modActive :: (a -> b) -> (Dynamic a -> Dynamic b) -> Active a -> Active b Source

Modify an Active value using a case analysis to see whether it is constant or dynamic.

runActive :: Active a -> Time -> a Source

Interpret an Active value as a function from time.

activeEra :: Active a -> Maybe Era Source

Get the Era of an Active value (or Nothing if it is a constant/pure value).

setEra :: Era -> Active a -> Active a Source

Set the era of an Active value. Note that this will change a constant Active into a dynamic one which happens to have the same value at all times.

atTime :: Time -> Active a -> Active a Source

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

Get the value of an Active a at the beginning of its era.

activeEnd :: Active a -> a Source

Get the value of an Active a at the end of its era.

Combinators

Special active values

ui :: Fractional a => Active a Source

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, and can be visualized as follows:

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

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

stretch s act "stretches" the active act so that it takes s times as long (retaining the same start time).

stretchTo :: Duration -> Active a -> Active a Source

stretchTo d stretches an Active so it has duration d. Has no effect if (1) d is non-positive, or (2) the Active value is constant, or (3) the Active value has zero duration.

during :: Active a -> Active a -> Active a Source

a1 `during` a2 stretches and shifts a1 so that it has the same era as a2. Has no effect if either of a1 or a2 are constant.

shift :: Duration -> Active a -> Active a Source

shift d act shifts the start time of act by duration d. Has no effect on constant values.

backwards :: Active a -> Active a Source

Reverse an active value so the start of its era gets mapped to the end and vice versa. For example, backwards ui can be visualized as

snapshot :: Time -> Active a -> Active a Source

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

"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 ui can be visualized as

See also clampBefore and clampAfter, which clamp only before or after the era, respectively.

clampBefore :: Active a -> Active a Source

"Clamp" an active value so that it is constant before the start of its era. For example, clampBefore ui can be visualized as

See the documentation of clamp for more information.

clampAfter :: Active a -> Active a Source

"Clamp" an active value so that it is constant after the end of its era. For example, clampBefore ui can be visualized as

See the documentation of clamp for more information.

trim :: Monoid a => Active a -> Active a Source

"Trim" an active value so that it is empty outside its era. trim has no effect on constant values.

For example, trim ui can be visualized as

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

"Trim" an active value so that it is empty before the start of its era. For example, trimBefore ui can be visualized as

See the documentation of trim for more details.

trimAfter :: Monoid a => Active a -> Active a Source

"Trim" an active value so that it is empty after the end of its era. For example, trimAfter ui can be visualized as

See the documentation of trim for more details.

Composing active values

after :: Active a -> Active a -> Active a Source

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.

(->>) :: Semigroup a => Active a -> Active a -> Active a infixr 5 Source

Sequence/overlay two Active values: shift the second to start immediately after the first (using after), then compose them (using <>).

(|>>) :: Active a -> Active a -> Active a Source

"Splice" two Active values together: shift the second to start immediately after the first (using after), and produce the value which acts like the first up to the common end/start point, then like the second after that. If both are constant, return the first.

movie :: [Active a] -> Active a Source

Splice together a list of active values using |>>. The list must be nonempty.

Discretization

discrete :: [a] -> Active a Source

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.