| Copyright | Written by David Himmelstrup | 
|---|---|
| License | Unlicense | 
| Maintainer | lemmih@gmail.com | 
| Stability | experimental | 
| Portability | POSIX | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Reanimate.Scene
Description
Scenes are an imperative way of defining animations.
Synopsis
- data Scene s a
- type ZIndex = Int
- sceneAnimation :: (forall s. Scene s a) -> Animation
- play :: Animation -> Scene s ()
- fork :: Scene s a -> Scene s a
- queryNow :: Scene s Time
- wait :: Duration -> Scene s ()
- waitUntil :: Time -> Scene s ()
- waitOn :: Scene s a -> Scene s a
- adjustZ :: (ZIndex -> ZIndex) -> Scene s a -> Scene s a
- withSceneDuration :: Scene s () -> Scene s Duration
- data Var s a
- newVar :: a -> Scene s (Var s a)
- readVar :: Var s a -> Scene s a
- writeVar :: Var s a -> a -> Scene s ()
- modifyVar :: Var s a -> (a -> a) -> Scene s ()
- tweenVar :: Var s a -> Duration -> (a -> Time -> a) -> Scene s ()
- tweenVarUnclamped :: Var s a -> Duration -> (a -> Time -> a) -> Scene s ()
- simpleVar :: (a -> SVG) -> a -> Scene s (Var s a)
- findVar :: (a -> Bool) -> [Var s a] -> Scene s (Var s a)
- data Sprite s
- data Frame s a
- unVar :: Var s a -> Frame s a
- spriteT :: Frame s Time
- spriteDuration :: Frame s Duration
- newSprite :: Frame s SVG -> Scene s (Sprite s)
- newSpriteA :: Animation -> Scene s (Sprite s)
- newSpriteA' :: Sync -> Animation -> Scene s (Sprite s)
- newSpriteSVG :: SVG -> Scene s (Sprite s)
- destroySprite :: Sprite s -> Scene s ()
- applyVar :: Var s a -> Sprite s -> (a -> SVG -> SVG) -> Scene s ()
- spriteModify :: Sprite s -> Frame s ((SVG, ZIndex) -> (SVG, ZIndex)) -> Scene s ()
- spriteMap :: Sprite s -> (SVG -> SVG) -> Scene s ()
- spriteTween :: Sprite s -> Duration -> (Double -> SVG -> SVG) -> Scene s ()
- spriteVar :: Sprite s -> a -> (a -> SVG -> SVG) -> Scene s (Var s a)
- spriteE :: Sprite s -> Effect -> Scene s ()
- spriteZ :: Sprite s -> ZIndex -> Scene s ()
- liftST :: ST s a -> Scene s a
Scenes
The ZIndex property specifies the stack order of sprites and animations. Elements with a higher ZIndex will be drawn on top of elements with a lower index.
sceneAnimation :: (forall s. Scene s a) -> Animation Source #
play :: Animation -> Scene s () Source #
Play an animation once and then remove it. This advances the clock by the duration of the animation.
Example:
do play drawBox play drawCircle

fork :: Scene s a -> Scene s a Source #
Execute actions in a scene without advancing the clock. Note that scenes do not end before all forked actions have completed.
Example:
do fork $ play drawBox play drawCircle

queryNow :: Scene s Time Source #
Query the current clock timestamp.
Example:
do now <- play drawCircle *> queryNow
   play $ staticFrame 1 $ scale 2 $ withStrokeWidth 0.05 $
     mkText $ "Now=" <> T.pack (show now)
wait :: Duration -> Scene s () Source #
Advance the clock by a given number of seconds.
Example:
do fork $ play drawBox wait 1 play drawCircle

waitOn :: Scene s a -> Scene s a Source #
Wait until all forked and sequential animations have finished.
Example:
do waitOn $ fork $ play drawBox play drawCircle

Variables
newVar :: a -> Scene s (Var s a) Source #
Create a new variable with a default value. Variables always have a defined value even if they are read at a timestamp that is earlier than when the variable was created. For example:
do v <- fork (wait 10 >> newVar 0) -- Create a variable at timestamp '10'.
   readVar v                       -- Read the variable at timestamp '0'.
                                   -- The value of the variable will be '0'.writeVar :: Var s a -> a -> Scene s () Source #
Write the value of a variable at the current timestamp.
Example:
do v <- newVar 0 newSprite $ mkCircle <$> unVar v writeVar v 1; wait 1 writeVar v 2; wait 1 writeVar v 3; wait 1

modifyVar :: Var s a -> (a -> a) -> Scene s () Source #
Modify the value of a variable at the current timestamp and all future timestamps.
tweenVar :: Var s a -> Duration -> (a -> Time -> a) -> Scene s () Source #
Modify a variable between now and now+duration.
   Note: The modification function is invoked for past timestamps (with a time value of 0) and
         for timestamps after now+duration (with a time value of 1). See tweenVarUnclamped.
tweenVarUnclamped :: Var s a -> Duration -> (a -> Time -> a) -> Scene s () Source #
Modify a variable between now and now+duration.
   Note: The modification function is invoked for past timestamps (with a negative time value) and
         for timestamps after now+duration (with a time value greater than 1).
simpleVar :: (a -> SVG) -> a -> Scene s (Var s a) Source #
Create and render a variable. The rendering will be born at the current timestamp and will persist until the end of the scene.
Example:
do var <- simpleVar mkCircle 0 tweenVar var 2 $ \val -> fromToS val (screenHeight/2)

findVar :: (a -> Bool) -> [Var s a] -> Scene s (Var s a) Source #
Helper function for filtering variables.
Sprites
Sprites are animations with a given time of birth as well as a time of death. They can be controlled using variables, tweening, and effects.
Sprite frame generator. Generates frames over time in a stateful environment.
unVar :: Var s a -> Frame s a Source #
Dereference a variable as a Sprite frame.
Example:
do v <- newVar 0 newSprite $ mkCircle <$> unVar v tweenVar v 1 $ \val -> fromToS val 3 tweenVar v 1 $ \val -> fromToS val 0

spriteDuration :: Frame s Duration Source #
Dereference duration of the current sprite.
newSprite :: Frame s SVG -> Scene s (Sprite s) Source #
Create new sprite defined by a frame generator. Unless otherwise specified using
   destroySprite, the sprite will die at the end of the scene.
Example:
do newSprite $ mkCircle <$> spriteT -- Circle sprite where radius=time. wait 2

newSpriteA :: Animation -> Scene s (Sprite s) Source #
Create a new sprite from an animation. This advances the clock by the
   duration of the animation. Unless otherwise specified using
   destroySprite, the sprite will die at the end of the scene.
Note: If the scene doesn't end immediately after the duration of the
   animation, the animation will be stretched to match the lifetime of the
   sprite. See newSpriteA' and play.
Example:
do fork $ newSpriteA drawCircle play drawBox play $ reverseA drawBox

newSpriteA' :: Sync -> Animation -> Scene s (Sprite s) Source #
Create a new sprite from an animation and specify the synchronization policy. This advances the clock by the duration of the animation.
Example:
do fork $ newSpriteA' SyncFreeze drawCircle play drawBox play $ reverseA drawBox

newSpriteSVG :: SVG -> Scene s (Sprite s) Source #
Create a sprite from a static SVG image.
Example:
do newSpriteSVG $ mkBackground "lightblue" play drawCircle

destroySprite :: Sprite s -> Scene s () Source #
Destroy a sprite, preventing it from being rendered in the future of the scene.
   If destroySprite is invoked multiple times, the earliest time-of-death is used.
Example:
do s <- newSpriteSVG $ withFillOpacity 1 $ mkCircle 1 fork $ wait 1 >> destroySprite s play drawBox

applyVar :: Var s a -> Sprite s -> (a -> SVG -> SVG) -> Scene s () Source #
Change the rendering of a sprite using data from a variable. If data from several variables is needed, use a frame generator instead.
Example:
do s <- fork $ newSpriteA drawBox v <- newVar 0 applyVar v s rotate tweenVar v 2 $ \val -> fromToS val 90

spriteModify :: Sprite s -> Frame s ((SVG, ZIndex) -> (SVG, ZIndex)) -> Scene s () Source #
Low-level frame modifier.
spriteMap :: Sprite s -> (SVG -> SVG) -> Scene s () Source #
Map the SVG output of a sprite.
Example:
do s <- fork $ newSpriteA drawCircle wait 1 spriteMap s flipYAxis

spriteTween :: Sprite s -> Duration -> (Double -> SVG -> SVG) -> Scene s () Source #
Modify the output of a sprite between now and now+duration.
Example:
do s <- fork $ newSpriteA drawCircle spriteTween s 1 $ \val -> translate (screenWidth*0.3*val) 0

spriteVar :: Sprite s -> a -> (a -> SVG -> SVG) -> Scene s (Var s a) Source #
Create a new variable and apply it to a sprite.
Example:
do s <- fork $ newSpriteA drawBox v <- spriteVar s 0 rotate tweenVar v 2 $ \val -> fromToS val 90

spriteE :: Sprite s -> Effect -> Scene s () Source #
Apply an effect to a sprite.
Example:
do s <- fork $ newSpriteA drawCircle spriteE s $ overBeginning 1 fadeInE spriteE s $ overEnding 0.5 fadeOutE

spriteZ :: Sprite s -> ZIndex -> Scene s () Source #
Set new ZIndex of a sprite.
Example:
do s1 <- newSpriteSVG $ withFillOpacity 1 $ withFillColor "blue" $ mkCircle 3 newSpriteSVG $ withFillOpacity 1 $ withFillColor "red" $ mkRect 8 3 wait 1 spriteZ s1 1 wait 1
