reanimate-1.1.6.0: Animation library based on SVGs.
CopyrightWritten by David Himmelstrup
LicenseUnlicense
Maintainerlemmih@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Reanimate.Scene

Description

Scenes are an imperative way of defining animations.

Synopsis

Scenes

data Scene s a Source #

A Scene represents a sequence of animations and variables that change over time.

Instances

Instances details
Monad (Scene s) Source # 
Instance details

Defined in Reanimate.Scene.Core

Methods

(>>=) :: Scene s a -> (a -> Scene s b) -> Scene s b #

(>>) :: Scene s a -> Scene s b -> Scene s b #

return :: a -> Scene s a #

Functor (Scene s) Source # 
Instance details

Defined in Reanimate.Scene.Core

Methods

fmap :: (a -> b) -> Scene s a -> Scene s b #

(<$) :: a -> Scene s b -> Scene s a #

MonadFix (Scene s) Source # 
Instance details

Defined in Reanimate.Scene.Core

Methods

mfix :: (a -> Scene s a) -> Scene s a #

Applicative (Scene s) Source # 
Instance details

Defined in Reanimate.Scene.Core

Methods

pure :: a -> Scene s a #

(<*>) :: Scene s (a -> b) -> Scene s a -> Scene s b #

liftA2 :: (a -> b -> c) -> Scene s a -> Scene s b -> Scene s c #

(*>) :: Scene s a -> Scene s b -> Scene s b #

(<*) :: Scene s a -> Scene s b -> Scene s a #

type ZIndex = Int Source #

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.

scene :: (forall s. Scene s a) -> Animation Source #

Render a Scene to an Animation.

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

waitUntil :: Time -> Scene s () Source #

Wait until the clock is equal to the given timestamp.

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

adjustZ :: (ZIndex -> ZIndex) -> Scene s a -> Scene s a Source #

Change the ZIndex of a scene.

withSceneDuration :: Scene s () -> Scene s Duration Source #

Query the duration of a scene.

signalS :: Sprite s -> Duration -> Signal -> Scene s () Source #

Apply easing function before rendering sprite.

Variables

data Var s a Source #

Time dependent variable.

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

readVar :: Var s a -> Scene s a Source #

Read the value of a variable at the current timestamp.

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.

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

data Sprite s Source #

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.

data Frame s a Source #

Sprite frame generator. Generates frames over time in a stateful environment.

Instances

Instances details
Functor (Frame s) Source # 
Instance details

Defined in Reanimate.Scene.Sprite

Methods

fmap :: (a -> b) -> Frame s a -> Frame s b #

(<$) :: a -> Frame s b -> Frame s a #

Applicative (Frame s) Source # 
Instance details

Defined in Reanimate.Scene.Sprite

Methods

pure :: a -> Frame s a #

(<*>) :: Frame s (a -> b) -> Frame s a -> Frame s b #

liftA2 :: (a -> b -> c) -> Frame s a -> Frame s b -> Frame s c #

(*>) :: Frame s a -> Frame s b -> Frame s b #

(<*) :: Frame s a -> Frame s b -> Frame s a #

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

spriteT :: Frame s Time Source #

Dereference seconds since sprite birth.

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

newSpritePart :: Frame s SVG -> Scene s (Sprite s) Source #

Create a new sprite defined by a frame generator, but not showing as part of the scene. Such sprites can be used hierarchically within the definitions of other sprites, via the function renderSprite.

newSprite_ :: Frame s SVG -> Scene s () Source #

Create new sprite defined by a frame generator. The sprite will die at the end of the scene.

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

newSpriteSVG_ :: SVG -> Scene s () Source #

Create a permanent sprite from a static SVG image. Same as newSpriteSVG but the sprite isn't returned and thus cannot be destroyed.

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

renderSprite :: Sprite s -> Frame s SVG Source #

Create a frame context from the source sprite for use within another. Use of this function allows several sprites to be combined into a single one, with the method of combination controled by variables.

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

spriteScope :: Scene s a -> Scene s a Source #

Destroy all local sprites at the end of a scene.

Example:

do -- the rect lives through the entire 3s animation
   newSpriteSVG_ $ translate (-3) 0 $ mkRect 4 4
   wait 1
   spriteScope $ do
     -- the circle only lives for 1 second.
     local <- newSpriteSVG $ translate 3 0 $ mkCircle 2
     spriteE local $ overBeginning 0.3 fadeInE
     spriteE local $ overEnding 0.3 fadeOutE
     wait 1
   wait 1

Object API

data Object s a Source #

Objects are SVG nodes (represented as Haskell values) with identity, location, and several other properties that can change over time.

data ObjectData a Source #

Container for object properties.

signalO :: Object s a -> Duration -> Signal -> Scene s () Source #

Apply easing function before rendering object.

oNew :: Renderable a => a -> Scene s (Object s a) Source #

Create new object.

newObject :: Renderable a => a -> Scene s (Object s a) Source #

Create new object.

newObjectPart :: Renderable a => a -> Scene s (Object s a) Source #

Create new object, but not showing as part of the scene, Such objects can be used hierachically within the definitions of sprites, via the function renderObject.

renderObject :: Object s a -> Frame s SVG Source #

Create a frame context from an object for use within a sprite definition.

Example:

do opacityVar <- newVar 1
   textObj1 <- newObjectPart $ scale 3 $ center $ latex Fade
   oModify textObj1 $ oContext .~ withFillColor "red"
   textObj2 <- newObjectPart $ scale 3 $ center $ latex Overlap
   oModify textObj2 $ oContext .~ withFillColor "blue"
   sprite <- newSprite $ do
     opacity <- unVar opacityVar
     text1 <- renderObject textObj1
     text2 <- renderObject textObj2
     return $ withGroupOpacity opacity $ mkGroup [text1, text2]
   fork $ oShowWith textObj1 $ setDuration 1 . oDraw
   wait 0.2
   fork $ oShowWith textObj2 $ setDuration 1 . oDraw
   wait 0.2
   tweenVar opacityVar 1 $ const $ fromToS 1 0

oModify :: Object s a -> (ObjectData a -> ObjectData a) -> Scene s () Source #

Modify object properties.

oModifyS :: Object s a -> State (ObjectData a) b -> Scene s () Source #

Modify object properties using a stateful API.

oRead :: Object s a -> Getting b (ObjectData a) b -> Scene s b Source #

Query object property.

oTween :: Object s a -> Duration -> (Double -> ObjectData a -> ObjectData a) -> Scene s () Source #

Modify object properties over a set duration.

oTweenS :: Object s a -> Duration -> (Double -> State (ObjectData a) b) -> Scene s () Source #

Modify object properties over a set duration using a stateful API.

oTweenV :: Renderable a => Object s a -> Duration -> (Double -> a -> a) -> Scene s () Source #

Modify object value over a set duration. This is a convenience function for modifying oValue.

oTweenVS :: Renderable a => Object s a -> Duration -> (Double -> State a b) -> Scene s () Source #

Modify object value over a set duration using a stateful API. This is a convenience function for modifying oValue.

class Renderable a where Source #

Objects can be any Haskell structure as long as it can be rendered to SVG.

Methods

toSVG :: a -> SVG Source #

Instances

Instances details
Renderable Tree Source # 
Instance details

Defined in Reanimate.Scene.Object

Methods

toSVG :: Tree -> SVG Source #

Renderable Camera Source # 
Instance details

Defined in Reanimate.Scene.Object

Methods

toSVG :: Camera -> SVG Source #

Renderable Morph Source # 
Instance details

Defined in Reanimate.Scene.Object

Methods

toSVG :: Morph -> SVG Source #

Renderable Rectangle Source # 
Instance details

Defined in Reanimate.Scene.Object

Methods

toSVG :: Rectangle -> SVG Source #

Renderable Circle Source # 
Instance details

Defined in Reanimate.Scene.Object

Methods

toSVG :: Circle -> SVG Source #

Object Properties

oTranslate :: Lens' (ObjectData a) (V2 Double) Source #

Object position. Default: <0,0>

oTranslateX :: Lens' (ObjectData a) Double Source #

Object X position. Default: 0

oTranslateY :: Lens' (ObjectData a) Double Source #

Object Y position. Default: 0

oSVG :: Getter (ObjectData a) SVG Source #

Rendered SVG node of an object. Does not include context or object properties. Read-only.

oContext :: Lens' (ObjectData a) (SVG -> SVG) Source #

Custom render context. Is applied to the object for every frame that it is shown.

oMargin :: Lens' (ObjectData a) (Double, Double, Double, Double) Source #

Object margins (top, right, bottom, left) in local units.

oMarginTop :: Lens' (ObjectData a) Double Source #

Object's top margin.

oMarginRight :: Lens' (ObjectData a) Double Source #

Object's right margin.

oMarginBottom :: Lens' (ObjectData a) Double Source #

Object's bottom margin.

oMarginLeft :: Lens' (ObjectData a) Double Source #

Object's left margin.

oBB :: Getter (ObjectData a) (Double, Double, Double, Double) Source #

Object bounding-box (minimal X-coordinate, minimal Y-coordinate, width, height). Uses boundingBox and has the same limitations.

oBBMinX :: Getter (ObjectData a) Double Source #

Object's minimal X-coordinate..

oBBMinY :: Getter (ObjectData a) Double Source #

Object's minimal Y-coordinate..

oBBWidth :: Getter (ObjectData a) Double Source #

Object's width without margin.

oBBHeight :: Getter (ObjectData a) Double Source #

Object's height without margin.

oOpacity :: Lens' (ObjectData a) Double Source #

Object opacity. Default: 1

oShown :: Lens' (ObjectData a) Bool Source #

Toggle for whether or not the object should be rendered. Default: False

oZIndex :: Lens' (ObjectData a) Int Source #

Object's z-index.

oEasing :: Lens' (ObjectData a) Signal Source #

Easing function used when modifying object properties. Default: curveS 2

oScale :: Lens' (ObjectData a) Double Source #

Object's scale. Default: 1

oScaleOrigin :: Lens' (ObjectData a) (V2 Double) Source #

Origin point for scaling. Default: <0,0>

oTopY :: Lens' (ObjectData a) Double Source #

Derived location of the top-most point of an object + margin.

oBottomY :: Lens' (ObjectData a) Double Source #

Derived location of the bottom-most point of an object + margin.

oLeftX :: Lens' (ObjectData a) Double Source #

Derived location of the left-most point of an object + margin.

oRightX :: Lens' (ObjectData a) Double Source #

Derived location of the right-most point of an object + margin.

oCenterXY :: Lens' (ObjectData a) (V2 Double) Source #

Derived location of an object's center point.

oCenterX :: Lens' (ObjectData a) Double Source #

Derived location of an object's center X value.

oCenterY :: Lens' (ObjectData a) Double Source #

Derived location of an object's center Y value.

oValue :: Renderable a => Lens' (ObjectData a) a Source #

Lens for the source value contained in an object.

Graphics object methods

oShow :: Object s a -> Scene s () Source #

Instantly show object.

oHide :: Object s a -> Scene s () Source #

Instantly hide object.

oShowWith :: Object s a -> (SVG -> Animation) -> Scene s () Source #

Show object with an animator function. The animator is responsible for transitioning the object from invisible to having its final shape. If this doesn't hold true for the animator function then the final animation will be discontinuous.

oHideWith :: Object s a -> (SVG -> Animation) -> Scene s () Source #

Hide object with an animator function. The animator is responsible for transitioning the object from visible to invisible. If this doesn't hold true for the animator function then the final animation will be discontinuous.

oFadeIn :: SVG -> Animation Source #

Fade in object over a set duration.

oFadeOut :: SVG -> Animation Source #

Fade out object over a set duration.

oGrow :: SVG -> Animation Source #

Scale in object over a set duration.

Example:

do txt <- oNew $ withStrokeWidth 0 $ withFillOpacity 1 $
     center $ scale 3 $ latex "oGrow"
   oShowWith txt oGrow
   wait 1; oHideWith txt oFadeOut

oShrink :: SVG -> Animation Source #

Scale out object over a set duration.

oTransform :: Object s a -> Object s b -> Duration -> Scene s () Source #

Morph source object into target object over a set duration.

type Origin = (Double, Double) Source #

Relative coordinates for an SVG node.

oScaleIn :: SVG -> Animation Source #

Scale in children from left to right, with an origin at the top of each child.

Example:

do txt <- oNew $ withStrokeWidth 0 $ withFillOpacity 1 $
     center $ scale 3 $ latex "oScaleIn"
   oShowWith txt $ adjustDuration (*2) . oScaleIn
   wait 1; oHideWith txt oFadeOut

oScaleIn' :: Signal -> Origin -> SVG -> Animation Source #

Like oScaleIn but takes an easing function and an origin.

oScaleOut :: SVG -> Animation Source #

Scale out children from left to right, with an origin at the bottom of each child.

Example:

do txt <- oNew $ withStrokeWidth 0 $ withFillOpacity 1 $
     center $ scale 3 $ latex "oScaleOut"
   oShowWith txt oFadeIn
   oHideWith txt $ adjustDuration (*2) . oScaleOut

oScaleOut' :: Signal -> Origin -> SVG -> Animation Source #

Like oScaleOut but takes an easing function and an origin.

oDraw :: SVG -> Animation Source #

Render SVG by first drawing outlines and then filling shapes.

Example:

do txt <- oNew $ withStrokeWidth 0 $ withFillOpacity 1 $
     center $ scale 4 $ latex "oDraw"
   oModify txt $ oEasing .~ id
   oShowWith txt oDraw; wait 1
   oHideWith txt oFadeOut

oSim :: (SVG -> Animation) -> SVG -> Animation Source #

Animate each child node in parallel.

oStagger :: (SVG -> Animation) -> SVG -> Animation Source #

Animate each child node in parallel, staggered by 0.2 seconds.

oStaggerRev :: (SVG -> Animation) -> SVG -> Animation Source #

Animate each child node in parallel, staggered by 0.2 seconds and in reverse order.

oStagger' :: Duration -> (SVG -> Animation) -> SVG -> Animation Source #

Animate each child node in parallel, staggered by a given duration.

oStaggerRev' :: Duration -> (SVG -> Animation) -> SVG -> Animation Source #

Animate each child node in parallel, staggered by given duration and in reverse order.

Pre-defined objects

newtype Circle Source #

Basic object mapping to <circle/> in SVG.

Constructors

Circle 

Instances

Instances details
Renderable Circle Source # 
Instance details

Defined in Reanimate.Scene.Object

Methods

toSVG :: Circle -> SVG Source #

circleRadius :: Lens' Circle Double Source #

Circle radius in local units.

data Rectangle Source #

Basic object mapping to <rect/> in SVG.

Constructors

Rectangle 

Instances

Instances details
Renderable Rectangle Source # 
Instance details

Defined in Reanimate.Scene.Object

Methods

toSVG :: Rectangle -> SVG Source #

rectWidth :: Lens' Rectangle Double Source #

Rectangle width in local units.

rectHeight :: Lens' Rectangle Double Source #

Rectangle height in local units.

data Morph Source #

Object representing an interpolation between SVG nodes.

Constructors

Morph 

Instances

Instances details
Renderable Morph Source # 
Instance details

Defined in Reanimate.Scene.Object

Methods

toSVG :: Morph -> SVG Source #

morphDelta :: Lens' Morph Double Source #

Control variable for the interpolation. A value of 0 gives the source SVG and 1 gives the target svg.

morphSrc :: Lens' Morph SVG Source #

Source shape.

morphDst :: Lens' Morph SVG Source #

Target shape.

data Camera Source #

Cameras can take control of objects and manipulate them with convenient pan and zoom operations.

Constructors

Camera 

Instances

Instances details
Renderable Camera Source # 
Instance details

Defined in Reanimate.Scene.Object

Methods

toSVG :: Camera -> SVG Source #

cameraAttach :: Object s Camera -> Object s a -> Scene s () Source #

Connect an object to a camera such that camera settings (position, zoom, and rotation) is applied to the object.

Example

do cam <- newObject Camera
   circ <- newObject $ Circle 2
   oModifyS circ $
     oContext .= withFillOpacity 1 . withFillColor "blue"
   oShow circ
   cameraAttach cam circ
   cameraZoom cam 1 2
   cameraZoom cam 1 1

cameraFocus :: Object s Camera -> V2 Double -> Scene s () Source #

Example

do cam <- newObject Camera
   circ <- newObject $ Circle 2; oShow circ
   oModify circ $ oTranslate .~ (-3,0)
   box <- newObject $ Rectangle 4 4; oShow box
   oModify box $ oTranslate .~ (3,0)
   cameraAttach cam circ
   cameraAttach cam box
   cameraFocus cam (-3,0)
   cameraZoom cam 2 2      -- Zoom in
   cameraZoom cam 2 1      -- Zoom out
   cameraFocus cam (3,0)
   cameraZoom cam 2 2      -- Zoom in
   cameraZoom cam 2 1      -- Zoom out

cameraSetZoom :: Object s Camera -> Double -> Scene s () Source #

Instantaneously set camera zoom level.

cameraZoom :: Object s Camera -> Duration -> Double -> Scene s () Source #

Change camera zoom level over a set duration.

cameraSetPan :: Object s Camera -> V2 Double -> Scene s () Source #

Instantaneously set camera location.

cameraPan :: Object s Camera -> Duration -> V2 Double -> Scene s () Source #

Change camera location over a set duration.

ST internals

liftST :: ST s a -> Scene s a Source #

Lift ST action into the Scene monad.

transitionO :: Transition -> Double -> (forall s'. Scene s' a) -> (forall s'. Scene s' b) -> Scene s () Source #

Apply a transformation with a given overlap. This makes sure to keep timestamps intact such that events can still be timed by transcripts.

evalScene :: (forall s. Scene s a) -> a Source #

Evaluate the value of a scene.