Introduction

This document will introduce the foundamental concepts used in reanimate. It is assumed that you are already familiar with Haskell. After reading, you will be able to understand all the concepts used in the API reference documentation. This is not a tutorial, though, and you may have to look at the examples before you can turn these concepts into beautiful animations.

For a bird's eye view on the design philosophy and capabilities of reanimate, see Gluing together animations. For help installing reanimate, see Getting started.

Animations as Executables

Reanimate animations are self-contained executables. These executables are capable of rendering the compiled animation in many different formats (mp4, gif, web) and with different resolutions and framerates. In other words, animations are agnostic with respect to the output format, the resolution, and the framerate.

By default, when you run the executable, the animation will open and play in a new browser window. Running the executable with render will create an .mp4 file with the same basename as the source file. For more details, have a look at the driver documentation.

Let's get our feet wet and have a look at an animation written with reanimate. By the way, all animations in this document are available from the examples/ folder in the project repository. Playing with the examples is a good way to learn.

We'll start with a minimal animation that prints "Hello world" on top of a cyan background, and then go over what the code means:

Toggle source code.
#!/usr/bin/env stack
-- stack runghc --package reanimate
{-# LANGUAGE OverloadedStrings #-}
import           Reanimate

main :: IO ()
main = reanimate $ addStatic (mkBackground "cyan") $ staticFrame 1 $ mkText "Hello world"
#!/usr/bin/env stack
-- stack runghc --package reanimate
{-# LANGUAGE OverloadedStrings #-}
import           Reanimate

main :: IO ()
main = reanimate $ addStatic (mkBackground "cyan") $ staticFrame 1 $ mkText "Hello world"

Let's go over the five library functions used by the Hello World animation:

The Canvas

The default SVG coordinate system places <0,0> in the top-left corner, sets width and height to match the output pixel resolution, and has the Y coordinate grow downwards. To make animations agnostic to resolution, reanimate uses its own coordinate system:

  • 16 units wide,
  • 9 units high,
  • 16/9 aspect ratio,
  • Y axis grows upwards,
  • X axis grows left to right,
  • <0,0> placed at center of screen.
Toggle source code.
#!/usr/bin/env stack
-- stack runghc --package reanimate
{-# LANGUAGE OverloadedStrings #-}
module Main
  ( main
  )
where

import           Data.Text                       (Text)
import qualified Data.Text                       as T
import           Graphics.SvgTree                hiding (Point, Text, height)
import           Linear.Metric
import           Linear.V2
import           Linear.Vector
import           Reanimate
import           Reanimate.Builtin.Documentation
import           Geom2D.CubicBezier.Linear
import           Text.Printf

main :: IO ()
main = reanimate $ scene $ do
  newSpriteSVG_ $ mkBackgroundPixel rtfdBackgroundColor
  newSpriteSVG_ static
  dotPath  <- newVar (QuadBezier (V2 0 0) (V2 0 0) (V2 0 0))
  dotParam <- newVar 0
  newSprite_ $ redDot <$> (evalBezier <$> unVar dotPath <*> unVar dotParam)
  let moveDot a b = do
        pos <- evalBezier <$> readVar dotPath <*> pure 1
        writeVar dotPath $ QuadBezier pos a b
        writeVar dotParam 0
        tweenVar dotParam 5 $ \v -> fromToS v 1 . curveS 2
        wait 1
  wait 1
  moveDot (V2 0 1)    (V2 4 2)
  moveDot (V2 (-1) 0) (V2 (-4) 3)
  moveDot (V2 0 0)  (V2 (-4) (-3))
  moveDot (V2 0 0)  (V2 5 (-2))
  moveDot (V2 6 2)  (V2 2 1)
  moveDot (V2 0 0)  (V2 0 0)

redDot :: V2 Double -> SVG
redDot (V2 x y) = translate x y $ mkGroup
  [ translate 0 (-0.5) $ scale 0.5 $ outlinedText $ T.pack $ printf "%.1f,%.1f" x y
  , withFillColor "red" $ mkCircle 0.1
  ]

static :: SVG
static = mkGroup
  [ grid
  , withStrokeColor "grey" $ mkLine (-screenWidth, 0) (screenWidth, 0)
  , withStrokeColor "grey" $ mkLine (0, -screenHeight) (0, screenHeight)
  , curlyBracket (V2 (-screenWidth / 2 + defaultStrokeWidth) (screenHeight / 2))
                 (V2 (screenWidth / 2 - defaultStrokeWidth) (screenHeight / 2))
                 1
  , translate 0 3 $ outlinedText "16 units"
  , curlyBracket (V2 (-screenWidth / 2) (-screenHeight / 2 + defaultStrokeWidth))
                 (V2 (-screenWidth / 2) (screenHeight / 2 - defaultStrokeWidth))
                 1
  , translate (-6.5) 0 $ rotate 90 $ outlinedText "9 units"
  ]

outlinedText :: Text -> SVG
outlinedText txt = mkGroup
  [ center
  $ withStrokeColorPixel rtfdBackgroundColor
  $ withStrokeWidth (defaultStrokeWidth * 8)
  $ withFillOpacity 0
  $ latex txt
  , center $ latex txt
  ]

curlyBracket :: RPoint -> RPoint -> Double -> SVG
curlyBracket from to height =
  withStrokeColor "black"
    $ withFillOpacity 0
    $ withStrokeWidth (defaultStrokeWidth * 2)
    $ mkPath
        [ MoveTo OriginAbsolute [from]
        , CurveTo OriginAbsolute [(from + outwards, halfway, halfway + outwards)]
        , CurveTo OriginAbsolute [(halfway, to + outwards, to)]
        ]
 where
  outwards = case normalize (from - to) ^* height of
    V2 x y -> V2 (-y) x
  halfway = lerp 0.5 from to

grid :: SVG
grid = withStrokeColor "grey" $ withStrokeWidth (defaultStrokeWidth * 0.5) $ mkGroup
  [ mkGroup
    [ translate
          0
          (i / screenHeight * screenHeight - screenHeight / 2 - screenHeight / 18)
        $ mkLine (-screenWidth, 0) (screenWidth, 0)
    | i <- [0 .. screenHeight]
    ]
  , mkGroup
    [ translate (i / screenWidth * screenWidth - screenWidth / 2) 0
        $ mkLine (0, -screenHeight) (0, screenHeight)
    | i <- [0 .. screenWidth]
    ]
  ]

Many of the SVG constructors such as mkCircle and mkRect do not take positioning arguments and are instead always centered at <0,0>. They can be moved with translate, though.

Also, if the default coordinate system or the 16/9 aspect ratio is unsuitable for your needs, they can easily be changed. See Custom viewports for details.

Animations

Animations describe how SVG frames change over a finite amount of time. There's both a declarative API and an imperative API for constructing and composing animations, and they are often used in conjunction with each other.

Signals

Signals are also called easing functions. They modify the rate of change for animations and mutable variables. Graphical examples are available in the API documentation. More examples are covered here.

Scenes

The scene API offers an imperative method for composing animations. It has sprites and mutable variables, yet is still free of side-effects and can be used freely with declarative combinators and effects.

Text and LaTeX

SVG text nodes can be undesirable for two reasons: (a) How they are rendered depends on available system fonts, (b) manipulating them as glyphs is difficult from Haskell (eg. finding the height of a text node or converting a text node to curves). Luckily, LaTeX can output SVG files. LaTeX is great at typesetting, especially for mathematics, but there are a few caveats:

  • Font metrics such as baseline, point size, ascender, descender, etc, are unavailable and aligning text is therefore more difficult.
  • SVG features such as wrapping text around a curve are unavailable.
  • Invoking LaTeX can be slow (taking a second or more).
  • LaTeX may be unavailable.

While most of these drawbacks are still unsolved, reanimate does have builtin caching that hides the cost of calling LaTeX.

Custom viewboxes

Reanimate defaults to a 16 by 9 aspect ratio but is capable of generating videos and GIFs of any resolution. You can create custom aspect ratios by scaling your animation to fit screenWidth by screenHeight, or by using the withViewBox helper function.


Toggle source code.
#!/usr/bin/env stack
-- stack runghc --package reanimate
{-# LANGUAGE OverloadedStrings #-}
module Main
  ( main
  )
where

import           Data.Text                       (Text)
import qualified Data.Text                       as T
import           Graphics.SvgTree                hiding (Text, height)
import           Linear.Metric
import           Linear.V2
import           Linear.Vector
import           Reanimate
import           Reanimate.Builtin.Documentation
import           Geom2D.CubicBezier.Linear
import           Text.Printf

newWidth, newHeight :: Double
newWidth = 8
newHeight = 8

main :: IO ()
main = reanimate $ mapA squareViewBox $ scene $ do
  newSpriteSVG_ $ mkBackgroundPixel rtfdBackgroundColor
  newSpriteSVG_ static
  dotPath  <- newVar (QuadBezier (V2 0 0) (V2 0 0) (V2 0 0))
  dotParam <- newVar 0
  newSprite_ $ redDot <$> (evalBezier <$> unVar dotPath <*> unVar dotParam)
  let moveDot a b = do
        pos <- evalBezier <$> readVar dotPath <*> pure 1
        writeVar dotPath $ QuadBezier pos a b
        writeVar dotParam 0
        tweenVar dotParam 5 $ \v -> fromToS v 1 . curveS 2
        wait 1
  moveDot (V2 0 1)     (V2 2 1)
  moveDot (V2 (-1) 0)  (V2 (-1) 1.5)
  moveDot (V2 0 0)   (V2 (-2) (-3))
  moveDot (V2 0 0)   (V2 2.5 (-1))
  moveDot (V2 3 1.5) (V2 1.5 1)
  moveDot (V2 0 0)   (V2 0 0)

squareViewBox :: SVG -> SVG
squareViewBox = withViewBox (-4, -4, 8, 8)

redDot :: V2 Double -> SVG
redDot (V2 x y) = translate x y $ mkGroup
  [ translate 0 (-0.5) $ scale 0.5 $ outlinedText $ T.pack $ printf "%.1f,%.1f" x y
  , withFillColor "red" $ mkCircle 0.1
  ]

static :: SVG
static = mkGroup
  [ grid
  , withStrokeColor "grey" $ mkLine (-screenWidth, 0) (screenWidth, 0)
  , withStrokeColor "grey" $ mkLine (0, -screenHeight) (0, screenHeight)
  , curlyBracket (V2 (-newWidth / 2 + defaultStrokeWidth) (newHeight / 2))
                 (V2 (newWidth / 2 - defaultStrokeWidth) (newHeight / 2))
                 1
  , translate 0 2.5 $ outlinedText "8 units"
  , curlyBracket (V2 (-newWidth / 2) (-newHeight / 2 + defaultStrokeWidth))
                 (V2 (-newWidth / 2) (newHeight / 2 - defaultStrokeWidth))
                 1
  , translate (-2.5) 0 $ rotate 90 $ outlinedText "8 units"
  ]

outlinedText :: Text -> SVG
outlinedText txt = mkGroup
  [ center
  $ withStrokeColorPixel rtfdBackgroundColor
  $ withStrokeWidth (defaultStrokeWidth * 8)
  $ withFillOpacity 0
  $ latex txt
  , center $ latex txt
  ]

curlyBracket :: RPoint -> RPoint -> Double -> SVG
curlyBracket from to height =
  withStrokeColor "black"
    $ withFillOpacity 0
    $ withStrokeWidth (defaultStrokeWidth * 2)
    $ mkPath
        [ MoveTo OriginAbsolute [from]
        , CurveTo OriginAbsolute [(from + outwards, halfway, halfway + outwards)]
        , CurveTo OriginAbsolute [(halfway, to + outwards, to)]
        ]
 where
  outwards = case normalize (from - to) ^* height of
    V2 x y -> V2 (-y) x
  halfway = lerp 0.5 from to

grid :: SVG
grid = withStrokeColor "grey" $ withStrokeWidth (defaultStrokeWidth * 0.5) $ mkGroup
  [ mkGroup
    [ translate
          0
          (i / screenHeight * screenHeight - screenHeight / 2 - screenHeight / 18)
        $ mkLine (-screenWidth, 0) (screenWidth, 0)
    | i <- [0 .. screenHeight]
    ]
  , mkGroup
    [ translate (i / screenWidth * screenWidth - screenWidth / 2) 0
        $ mkLine (0, -screenHeight) (0, screenHeight)
    | i <- [0 .. screenWidth]
    ]
  ]