Copyright | (c) 2016 Schell Scivally |
---|---|
License | MIT |
Maintainer | Schell Scivally <schell@takt.com> |
Safe Haskell | None |
Language | Haskell2010 |
Tweening is a technique of generating intermediate samples of a type between a start and end value. By sampling a running tween each frame we get a smooth animation of a value over time.
At first release varying
is only capable of tweening numerical
values of type (Fractional t, Ord t) => t
that match the type of
time you use. At some point it would be great to be able to tween
arbitrary types, and possibly tween one type into another (pipe
dreams).
Synopsis
- type Easing t f = t -> f -> t -> t
- data TweenT f t m a
- type Tween f t a = TweenT f t Identity a
- tween :: (Monad m, Real t, Real f, Fractional f) => Easing t f -> t -> t -> f -> TweenT f t m t
- tween_ :: (Monad m, Real t, Real f, Fractional f) => Easing t f -> t -> t -> f -> TweenT f t m ()
- constant :: (Monad m, Num t, Ord t) => a -> t -> TweenT t a m a
- withTween :: (Monad m, Real t, Real a, Fractional a) => Easing t a -> t -> t -> a -> (t -> x) -> TweenT a x m t
- withTween_ :: (Monad m, Real t, Real a, Fractional a) => Easing t a -> t -> t -> a -> (t -> x) -> TweenT a x m ()
- linear :: (Floating t, Real f) => Easing t f
- easeInCirc :: (Floating t, Real f, Floating f) => Easing t f
- easeOutCirc :: (Floating t, Real f) => Easing t f
- easeInExpo :: (Floating t, Real f) => Easing t f
- easeOutExpo :: (Floating t, Real f) => Easing t f
- easeInSine :: (Floating t, Real f) => Easing t f
- easeOutSine :: (Floating t, Real f) => Easing t f
- easeInOutSine :: (Floating t, Real f) => Easing t f
- easeInPow :: (Fractional t, Real f) => Int -> Easing t f
- easeOutPow :: (Fractional t, Real f) => Int -> Easing t f
- easeInCubic :: (Fractional t, Real f) => Easing t f
- easeOutCubic :: (Fractional t, Real f) => Easing t f
- easeInQuad :: (Fractional t, Real f) => Easing t f
- easeOutQuad :: (Fractional t, Real f) => Easing t f
- tweenStream :: forall m f t x. (Functor m, Monad m, Num f) => TweenT f t m x -> t -> VarT m f t
- runTweenT :: Functor m => TweenT f t m a -> f -> f -> m (Either a (t, TweenT f t m a), f)
- scanTween :: (Monad m, Num f) => TweenT f t m a -> t -> [f] -> m [t]
Tweening types
type Easing t f = t -> f -> t -> t Source #
An easing function. The parameters are often named c
, t
and b
,
where c
is the total change in value over the complete duration
(endValue - startValue), t
is the current percentage (0 to 1) of the
duration that has elapsed and b
is the start value.
To make things simple only numerical values can be tweened and the type of time deltas must match the tween's value type. This may change in the future :)
A TweenT
is a SplineT
that holds a duration in local state. This allows
TweenT
s to be sequenced monadically.
f
is the input time delta type (the input type)t
is the start and end value type (the output type)a
is the result value type
You can sequence TweenT
s with monadic notation to produce more complex ones.
This is especially useful for animation:
>>>
:{
let tweenInOutExpo :: ( Monad m, Floating t, Real t, Real f, Fractional f ) => t -> t -> f -> TweenT f t m t tweenInOutExpo start end dur = do x <- tween easeInExpo start (end/2) (dur/2) tween easeOutExpo x end $ dur/2>>>
:}
Instances
MonadTrans (TweenT f t) Source # | |
Defined in Control.Varying.Tween | |
Monad m => Monad (TweenT f t m) Source # | |
Monad m => Functor (TweenT f t m) Source # | |
Monad m => Applicative (TweenT f t m) Source # | |
Defined in Control.Varying.Tween | |
Generic (TweenT f t m a) Source # | |
type Rep (TweenT f t m a) Source # | |
Defined in Control.Varying.Tween |
Creating tweens
The most direct route toward tweening values is to use tween
along with an interpolation function such as easeInExpo
. For example,
tween easeInExpo 0 100 10
, this will create a spline that produces a
number interpolated from 0 to 100 over 10 seconds. At the end of the
tween the spline will return the result value.
tween :: (Monad m, Real t, Real f, Fractional f) => Easing t f -> t -> t -> f -> TweenT f t m t Source #
Creates a spline that produces a value interpolated between a start and
end value using an easing equation (Easing
) over a duration. The
resulting spline will take a time delta as input.
Keep in mind that tween
must be fed time deltas, not absolute time or
duration. This is mentioned because the author has made that mistake
more than once ;)
tween
concludes returning the latest output value.
tween_ :: (Monad m, Real t, Real f, Fractional f) => Easing t f -> t -> t -> f -> TweenT f t m () Source #
A version of tween
that discards the result. It is simply
tween f a b c >> return ()
constant :: (Monad m, Num t, Ord t) => a -> t -> TweenT t a m a Source #
Creates a tween that performs no interpolation over the duration.
withTween :: (Monad m, Real t, Real a, Fractional a) => Easing t a -> t -> t -> a -> (t -> x) -> TweenT a x m t Source #
A version of tween
that maps its output using the given constant
function.
withTween ease from to dur f = mapOutput (pure f) $ tween ease from to dur
withTween_ :: (Monad m, Real t, Real a, Fractional a) => Easing t a -> t -> t -> a -> (t -> x) -> TweenT a x m () Source #
A version of withTween
that discards its result.
Combining tweens
These pure functions take a c
(total change in value, ie end - start),
t
(percent of duration completion) and b
(start value) and result in
an interpolation of a value. To see what these look like please check
out http://www.gizma.com/easing/.
easeOutPow :: (Fractional t, Real f) => Int -> Easing t f Source #
Ease out by some power.
easeInCubic :: (Fractional t, Real f) => Easing t f Source #
Ease in cubic.
easeOutCubic :: (Fractional t, Real f) => Easing t f Source #
Ease out cubic.
easeInQuad :: (Fractional t, Real f) => Easing t f Source #
Ease in quadratic.
easeOutQuad :: (Fractional t, Real f) => Easing t f Source #
Ease out quadratic.
Running tweens
:: (Functor m, Monad m, Num f) | |
=> TweenT f t m x | The tween to convert into a stream |
-> t | An initial output value |
-> VarT m f t |
Converts a tween into a continuous value stream. This is the tween version
of outputStream
. This is the preferred way to run
your tweens.
>>>
:{
let x :: TweenT Float Float IO Float x = tween linear 0 1 1 y :: TweenT Float Float IO Float y = tween linear 0 1 2 v :: VarT IO Float (Float, Float) v = (,) <$> tweenStream x 0 <*> tweenStream y 0 in testVarOver v [0.5, 0.5, 0.5, 0.5]>>>
:}
(0.5,0.25) (1.0,0.5) (1.0,0.75) (1.0,1.0)
:: Functor m | |
=> TweenT f t m a | |
-> f | The input time delta this frame |
-> f | The leftover time delta from last frame |
-> m (Either a (t, TweenT f t m a), f) | Returns
|