Copyright | Written by David Himmelstrup |
---|---|
License | Unlicense |
Maintainer | lemmih@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- reanimate :: Animation -> IO ()
- type SVG = Tree
- type Time = Double
- data Animation = Animation Duration (Time -> SVG)
- mkAnimation :: Duration -> (Time -> SVG) -> Animation
- animate :: (Time -> SVG) -> Animation
- staticFrame :: Duration -> SVG -> Animation
- duration :: Animation -> Duration
- frameAt :: Time -> Animation -> SVG
- seqA :: Animation -> Animation -> Animation
- parA :: Animation -> Animation -> Animation
- parLoopA :: Animation -> Animation -> Animation
- parDropA :: Animation -> Animation -> Animation
- pause :: Duration -> Animation
- andThen :: Animation -> Animation -> Animation
- mapA :: (SVG -> SVG) -> 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
- addStatic :: SVG -> 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
- 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 ()
- type Effect = Duration -> Time -> Tree -> Tree
- overBeginning :: Duration -> Effect -> Effect
- overEnding :: Duration -> Effect -> Effect
- overInterval :: Time -> Time -> Effect -> Effect
- reverseE :: Effect -> Effect
- delayE :: Duration -> Effect -> Effect
- applyE :: Effect -> Animation -> Animation
- constE :: (Tree -> Tree) -> Effect
- fadeInE :: Effect
- fadeOutE :: Effect
- fadeLineInE :: Double -> Effect
- fadeLineOutE :: Double -> Effect
- drawInE :: Effect
- drawOutE :: Effect
- fillInE :: Effect
- scaleE :: Double -> Effect
- translateE :: Double -> Double -> Effect
- aroundCenterE :: Effect -> Effect
- 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
- svgAsPngFile :: Tree -> FilePath
- vectorize :: FilePath -> Tree
- vectorize_ :: [String] -> FilePath -> Tree
- latex :: Text -> Tree
- latexAlign :: Text -> Tree
- xelatex :: Text -> Tree
- povray :: [String] -> Text -> Tree
- povray' :: [String] -> Text -> FilePath
- blender :: Text -> SVG
- blender' :: Text -> FilePath
- 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
- pFPS :: FPS
- pHeight :: Height
- pWidth :: Width
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 reaches 60 fps.
- Key commands for pausing, frame stepping, forward/rewind. To pause press SPACE, to move -1/+1/-10/+10 frames use LEFT/RIGHT/DOWN/UP arrow keys.
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 text
Animations
staticFrame :: Duration -> SVG -> Animation Source #
Create an animation with provided duration
, which consists of stationary frame displayed for its entire duration.
frameAt :: Time -> Animation -> SVG Source #
Calculate the frame that would be displayed at given point in time
of running animation
.
The provided time parameter is clamped between 0 and animation duration.
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 :: (SVG -> SVG) -> 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
:: Time | value between 0 and 1. The frame displayed at this point in the original animation will be displayed for the duration of the new animation |
-> Animation | original animation, from which the frame will be taken |
-> Animation | new animation consisting of static frame displayed for the duration of the original animation |
freezeAtPercentage time animation
creates an animation consisting of stationary frame,
that would be displayed in the provided animation
at given time
.
The duration of the new animation is the same as the duration of provided animation
.
addStatic :: SVG -> Animation -> Animation Source #
Overlay animation on top of static SVG image.
Example:
addStatic (mkBackground "lightblue") 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
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
Effects
= Duration | Duration of the effect (in seconds) |
-> Time | Time elapsed from when the effect started (in seconds) |
-> Tree | Image to be modified |
-> Tree | Image after modification |
An Effect represents a modification of a SVG Tree
that can vary with time.
:: Duration | Duration of the initial segment of the animation over which the Effect should be applied |
-> Effect | The Effect to modify |
-> Effect | Effect which will only affect the initial segment of the animation |
Modify the effect so that it only applies to the initial part of the animation.
:: Duration | Duration of the ending segment of the animation over which the Effect should be applied |
-> Effect | The Effect to modify |
-> Effect | Effect which will only affect the ending segment of the animation |
Modify the effect so that it only applies to the ending part of the animation.
:: Time | time after start of animation when the effect should start |
-> Time | time after start of the animation when the effect should finish |
-> Effect | The Effect to modify |
-> Effect | Effect which will only affect the specified interval within the animation |
Modify the effect so that it only applies within given interval of animation's running time.
delayE :: Duration -> Effect -> Effect Source #
Delay the effect so that it only starts after specified duration and then runs till the end of animation.
applyE :: Effect -> Animation -> Animation Source #
Modify the animation by applying the effect. If desired, you can apply multiple effects to single animation by calling this function multiple times.
constE :: (Tree -> Tree) -> Effect Source #
Build an effect from an image-modifying function. This effect does not change as time passes.
fadeLineInE :: Double -> Effect Source #
Change stroke width from 0 to given value.
fadeLineOutE :: Double -> Effect Source #
Change stroke width from given value to 0. Reverse of fadeLineInE
.
Effect of progressively drawing the image. Note that this will only affect primitive shapes (see pathify
).
translateE :: Double -> Double -> Effect Source #
Move the image from its current position to the target x y coordinates.
aroundCenterE :: Effect -> Effect Source #
Transform the effect so that the image passed to the effect's image-modifying
function has coordinates (0, 0) shifted to the center of its bounding box.
Also see aroundCenter
.
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 #
svgAsPngFile :: Tree -> FilePath 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 "中文"
External 3D renderers
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 #