varying-0.8.1.0: FRP through value streams and monadic splines.

Copyright(c) 2016 Schell Scivally
LicenseMIT
MaintainerSchell Scivally <schell@takt.com>
Safe HaskellNone
LanguageHaskell2010

Control.Varying.Tween

Contents

Description

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

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 :)

data TweenT f t m a Source #

A TweenT is a SplineT that holds a duration in local state. This allows TweenTs 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 TweenTs 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 # 
Instance details

Defined in Control.Varying.Tween

Methods

lift :: Monad m => m a -> TweenT f t m a #

Monad m => Monad (TweenT f t m) Source # 
Instance details

Defined in Control.Varying.Tween

Methods

(>>=) :: TweenT f t m a -> (a -> TweenT f t m b) -> TweenT f t m b #

(>>) :: TweenT f t m a -> TweenT f t m b -> TweenT f t m b #

return :: a -> TweenT f t m a #

fail :: String -> TweenT f t m a #

Monad m => Functor (TweenT f t m) Source # 
Instance details

Defined in Control.Varying.Tween

Methods

fmap :: (a -> b) -> TweenT f t m a -> TweenT f t m b #

(<$) :: a -> TweenT f t m b -> TweenT f t m a #

Monad m => Applicative (TweenT f t m) Source # 
Instance details

Defined in Control.Varying.Tween

Methods

pure :: a -> TweenT f t m a #

(<*>) :: TweenT f t m (a -> b) -> TweenT f t m a -> TweenT f t m b #

liftA2 :: (a -> b -> c) -> TweenT f t m a -> TweenT f t m b -> TweenT f t m c #

(*>) :: TweenT f t m a -> TweenT f t m b -> TweenT f t m b #

(<*) :: TweenT f t m a -> TweenT f t m b -> TweenT f t m a #

Generic (TweenT f t m a) Source # 
Instance details

Defined in Control.Varying.Tween

Associated Types

type Rep (TweenT f t m a) :: Type -> Type #

Methods

from :: TweenT f t m a -> Rep (TweenT f t m a) x #

to :: Rep (TweenT f t m a) x -> TweenT f t m a #

type Rep (TweenT f t m a) Source # 
Instance details

Defined in Control.Varying.Tween

type Rep (TweenT f t m a) = D1 (MetaData "TweenT" "Control.Varying.Tween" "varying-0.8.1.0-6aQUJPxqjqyxRwV7D79Ld" True) (C1 (MetaCons "TweenT" PrefixI True) (S1 (MetaSel (Just "unTweenT") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SplineT f t (StateT f m) a))))

type Tween f t a = TweenT f t Identity a Source #

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/.

linear :: (Floating t, Real f) => Easing t f Source #

Ease linear.

easeInCirc :: (Floating t, Real f, Floating f) => Easing t f Source #

Ease in circular.

easeOutCirc :: (Floating t, Real f) => Easing t f Source #

Ease out circular.

easeInExpo :: (Floating t, Real f) => Easing t f Source #

Ease in exponential.

easeOutExpo :: (Floating t, Real f) => Easing t f Source #

Ease out exponential.

easeInSine :: (Floating t, Real f) => Easing t f Source #

Ease in sinusoidal.

easeOutSine :: (Floating t, Real f) => Easing t f Source #

Ease out sinusoidal.

easeInOutSine :: (Floating t, Real f) => Easing t f Source #

Ease in and out sinusoidal.

easeInPow :: (Fractional t, Real f) => Int -> Easing t f Source #

Ease in by some power.

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

tweenStream Source #

Arguments

:: (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)

runTweenT Source #

Arguments

:: 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 a tuple of either the result or a tuple of this step's output value and the tween for the next step and the leftover time delta for the next step

scanTween :: (Monad m, Num f) => TweenT f t m a -> t -> [f] -> m [t] Source #