| Copyright | Written by David Himmelstrup |
|---|---|
| License | Unlicense |
| Maintainer | lemmih@gmail.com |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Reanimate
Contents
Description
Synopsis
- reanimate :: Animation -> IO ()
- type SVG = Tree
- data Animation = Animation Duration (Time -> SVG)
- mkAnimation :: Duration -> (Time -> SVG) -> Animation
- animate :: (Time -> SVG) -> Animation
- duration :: Animation -> Duration
- seqA :: Animation -> Animation -> Animation
- parA :: Animation -> Animation -> Animation
- parLoopA :: Animation -> Animation -> Animation
- parDropA :: Animation -> Animation -> Animation
- pause :: Duration -> Animation
- andThen :: Animation -> Animation -> Animation
- mapA :: (Tree -> Tree) -> Animation -> Animation
- pauseAtEnd :: Duration -> Animation -> Animation
- pauseAtBeginning :: Duration -> Animation -> Animation
- pauseAround :: Duration -> Duration -> Animation -> Animation
- adjustDuration :: (Duration -> Duration) -> Animation -> Animation
- setDuration :: Duration -> Animation -> Animation
- reverseA :: Animation -> Animation
- playThenReverseA :: Animation -> Animation
- repeatA :: Double -> Animation -> Animation
- freezeAtPercentage :: Time -> Animation -> Animation
- signalA :: Signal -> Animation -> Animation
- type Signal = Double -> Double
- constantS :: Double -> Signal
- fromToS :: Double -> Double -> Signal
- reverseS :: Signal
- curveS :: Double -> Signal
- bellS :: Double -> Signal
- oscillateS :: Signal
- fromListS :: [(Double, Signal)] -> Signal
- (#) :: a -> (a -> b) -> b
- type ZIndex = Int
- data Scene s a
- sceneAnimation :: (forall s. Scene s a) -> Animation
- fork :: Scene s a -> Scene s a
- play :: Animation -> Scene s ()
- playZ :: ZIndex -> Animation -> Scene s ()
- queryNow :: Scene s Time
- waitAll :: Scene s a -> Scene s a
- waitUntil :: Time -> Scene s ()
- wait :: Duration -> Scene s ()
- adjustZ :: (ZIndex -> ZIndex) -> Scene s a -> Scene s a
- withSceneDuration :: Scene s () -> Scene s Duration
- module Reanimate.Svg.Constructors
- module Reanimate.Svg.LineCommand
- module Reanimate.Svg.BoundingBox
- module Reanimate.Svg
- embedImage :: PngSavable a => Image a -> Tree
- embedDynamicImage :: DynamicImage -> Tree
- embedPng :: Double -> Double -> ByteString -> Tree
- raster :: Tree -> DynamicImage
- latex :: Text -> Tree
- latexAlign :: Text -> Tree
- xelatex :: Text -> Tree
- povray :: [String] -> Text -> Tree
- turbo :: Double -> PixelRGB8
- viridis :: Double -> PixelRGB8
- magma :: Double -> PixelRGB8
- inferno :: Double -> PixelRGB8
- plasma :: Double -> PixelRGB8
- sinebow :: Double -> PixelRGB8
- parula :: Double -> PixelRGB8
- cividis :: Double -> PixelRGB8
- jet :: Double -> PixelRGB8
- hsv :: Double -> PixelRGB8
- hsvMatlab :: Double -> PixelRGB8
- greyscale :: Double -> PixelRGB8
- screenWidth :: Num a => a
- screenHeight :: Num a => a
- defaultDPI :: Dpi
- defaultStrokeWidth :: Double
Driver
Reanimate features a web-based viewer which is opened by default if no other parameters are given. Key features:
- This viewer listens for changes to the source file and recompiles the code automatically as needed.
- Animations are rendered with increasing fidelity until the frame rate eaches 60 fps.
- Key commands for pausing, frame stepping, forward/rewind.
reanimate :: Animation -> IO () Source #
Main entry-point for accessing an animation. Creates a program that takes the following command-line arguments:
Usage: PROG [COMMAND]
This program contains an animation which can either be viewed in a web-browser
or rendered to disk.
Available options:
-h,--help Show this help text
Available commands:
check Run a system's diagnostic and report any missing
external dependencies.
view Play animation in browser window.
render Render animation to file.Neither the check nor the view command take any additional arguments.
Rendering animation can be controlled with these arguments:
Usage: PROG render [-o|--target FILE] [--fps FPS] [-w|--width PIXELS]
[-h|--height PIXELS] [--compile] [--format FMT]
[--preset TYPE]
Render animation to file.
Available options:
-o,--target FILE Write output to FILE
--fps FPS Set frames per second.
-w,--width PIXELS Set video width.
-h,--height PIXELS Set video height.
--compile Compile source code before rendering.
--format FMT Video format: mp4, gif, webm
--preset TYPE Parameter presets: youtube, gif, quick
-h,--help Show this help textAnimations
Animations are SVGs over a finite time.
Composition
seqA :: Animation -> Animation -> Animation Source #
Play animations in sequence. The lhs animation is removed after it has
completed. New animation duration is 'duration lhs + duration rhs'.
Example:
drawBox `seqA` drawCircle

parA :: Animation -> Animation -> Animation Source #
Play two animation concurrently. Shortest animation freezes on last frame.
New animation duration is 'max (duration lhs) (duration rhs)'.
Example:
drawBox `parA` adjustDuration (*2) drawCircle

parLoopA :: Animation -> Animation -> Animation Source #
Play two animation concurrently. Shortest animation loops.
New animation duration is 'max (duration lhs) (duration rhs)'.
Example:
drawBox `parLoopA` adjustDuration (*2) drawCircle

parDropA :: Animation -> Animation -> Animation Source #
Play two animation concurrently. Animations disappear after playing once.
New animation duration is 'max (duration lhs) (duration rhs)'.
Example:
drawBox `parLoopA` adjustDuration (*2) drawCircle

pause :: Duration -> Animation Source #
Empty animation (no SVG output) with a fixed duration.
Example:
pause 1 `seqA` drawProgress

andThen :: Animation -> Animation -> Animation Source #
Play left animation and freeze on the last frame, then play the right
animation. New duration is 'duration lhs + duration rhs'.
Example:
drawBox `andThen` drawCircle

mapA :: (Tree -> Tree) -> Animation -> Animation Source #
Map over the SVG produced by an animation at every frame.
Example:
mapA (scale 0.5) drawCircle

pauseAtEnd :: Duration -> Animation -> Animation Source #
Freeze the last frame for t seconds at the end of the animation.
Example:
pauseAtEnd 1 drawProgress

pauseAtBeginning :: Duration -> Animation -> Animation Source #
Freeze the first frame for t seconds at the beginning of the animation.
Example:
pauseAtBeginning 1 drawProgress

pauseAround :: Duration -> Duration -> Animation -> Animation Source #
Freeze the first and the last frame of the animation for a specified duration.
Example:
pauseAround 1 1 drawProgress

adjustDuration :: (Duration -> Duration) -> Animation -> Animation Source #
Change the duration of an animation. Animates are stretched or squished (rather than truncated) to fit the new duration.
setDuration :: Duration -> Animation -> Animation Source #
Set the duration of an animation by adjusting its playback rate. The animation is still played from start to finish without being cropped.
playThenReverseA :: Animation -> Animation Source #
Play animation before playing it again in reverse. Duration is twice the duration of the input.
Example:
playThenReverseA drawCircle

repeatA :: Double -> Animation -> Animation Source #
Loop animation n number of times. This number may be fractional and it
may be less than 1. It must be greater than or equal to 0, though.
New duration is n*duration input.
Example:
repeatA 1.5 drawCircle

signalA :: Signal -> Animation -> Animation Source #
Modify the time component of an animation. Animation duration is unchanged.
Example:
signalA (fromToS 0.25 0.75) drawCircle

Signals
type Signal = Double -> Double Source #
Signals are time-varying variables. Signals can be composed using function composition.
fromToS :: Double -> Double -> Signal Source #
Signal with new starting and end values.
Example:
signalA (fromToS 0.8 0.2) drawProgress

curveS :: Double -> Signal Source #
S-curve signal. Takes a steepness parameter. 2 is a good default.
Example:
signalA (curveS 2) drawProgress

bellS :: Double -> Signal Source #
Bell-curve signal. Takes a steepness parameter. 2 is a good default.
Example:
signalA (bellS 2) drawProgress

oscillateS :: Signal Source #
Oscillate signal.
Example:
signalA oscillateS drawProgress

Scenes
sceneAnimation :: (forall s. Scene s a) -> Animation Source #
SVG
module Reanimate.Svg.Constructors
module Reanimate.Svg.LineCommand
module Reanimate.Svg.BoundingBox
module Reanimate.Svg
Raster data
embedImage :: PngSavable a => Image a -> Tree Source #
embedDynamicImage :: DynamicImage -> Tree Source #
raster :: Tree -> DynamicImage Source #
External SVG providers
latex :: Text -> Tree Source #
Invoke latex and import the result as an SVG object. SVG objects are cached to improve performance.
Example:
latex "$e^{i\\pi}+1=0$"
latexAlign :: Text -> Tree Source #
Invoke latex and import the result as an SVG object. SVG objects are cached to improve performance. This wraps the TeX code in an 'align*' context.
Example:
latexAlign "R = \\frac{{\\Delta x}}{{kA}}"
xelatex :: Text -> Tree Source #
Invoke xelatex and import the result as an SVG object. SVG objects are cached to improve performance. Xelatex has support for non-western scripts.
Example:
xelatex "中文"

Colormaps
turbo :: Double -> PixelRGB8 Source #
Given a number t in the range [0,1], returns the corresponding color from the “turbo” color scheme by Anton Mikhailov.

viridis :: Double -> PixelRGB8 Source #
Given a number t in the range [0,1], returns the corresponding color from the “viridis” perceptually-uniform color scheme designed by van der Walt, Smith and Firing for matplotlib, represented as an RGB string.

magma :: Double -> PixelRGB8 Source #
Given a number t in the range [0,1], returns the corresponding color from the “magma” perceptually-uniform color scheme designed by van der Walt and Smith for matplotlib, represented as an RGB string.

inferno :: Double -> PixelRGB8 Source #
Given a number t in the range [0,1], returns the corresponding color from the “inferno” perceptually-uniform color scheme designed by van der Walt and Smith for matplotlib, represented as an RGB string.

plasma :: Double -> PixelRGB8 Source #
Given a number t in the range [0,1], returns the corresponding color from the “plasma” perceptually-uniform color scheme designed by van der Walt and Smith for matplotlib, represented as an RGB string.

sinebow :: Double -> PixelRGB8 Source #
Given a number t in the range [0,1], returns the corresponding color from the “sinebow” color scheme by Jim Bumgardner and Charlie Loyd.

cividis :: Double -> PixelRGB8 Source #
Given a number t in the range [0,1], returns the corresponding color from the “cividis” color vision deficiency-optimized color scheme designed by Nuñez, Anderton, and Renslow, represented as an RGB string.

Constants
screenWidth :: Num a => a Source #
screenHeight :: Num a => a Source #
defaultDPI :: Dpi Source #







