Commit d5c97ea3 authored by Sumit Sahrawat's avatar Sumit Sahrawat

Fix #350 -- Show diagrams Animations as animated .gif images

parent b0bca8ae
{-# LANGUAGE NoImplicitPrelude, TypeSynonymInstances, FlexibleInstances #-} {-# LANGUAGE NoImplicitPrelude, TypeSynonymInstances, FlexibleInstances #-}
module IHaskell.Display.Diagrams (diagram) where module IHaskell.Display.Diagrams (diagram, animation) where
import ClassyPrelude import ClassyPrelude
...@@ -11,6 +11,7 @@ import Diagrams.Prelude ...@@ -11,6 +11,7 @@ import Diagrams.Prelude
import Diagrams.Backend.Cairo import Diagrams.Backend.Cairo
import IHaskell.Display import IHaskell.Display
import IHaskell.Display.Diagrams.Animation
instance IHaskellDisplay (QDiagram Cairo R2 Any) where instance IHaskellDisplay (QDiagram Cairo R2 Any) where
display renderable = do display renderable = do
......
{-# LANGUAGE NoImplicitPrelude, TypeSynonymInstances, FlexibleInstances #-}
module IHaskell.Display.Diagrams.Animation (animation) where
import ClassyPrelude hiding (filename)
import Diagrams.Prelude
import Diagrams.Backend.Cairo
import Diagrams.Backend.Cairo.CmdLine (GifOpts (..))
import Diagrams.Backend.CmdLine (DiagramOpts (..), mainRender)
import IHaskell.Display
instance IHaskellDisplay (QAnimation Cairo R2 Any) where
display renderable = do
gif <- animationData renderable
return $ Display [html $ "<img src=\"data:image/gif;base64,"
++ gif ++ "\" />"]
animationData :: Animation Cairo R2 -> IO String
animationData renderable = do
switchToTmpDir
-- Generate the frames
let fps = 30
animAdjusted = animEnvelope' fps renderable
frames = simulate fps animAdjusted
timediff = 100 `div` ceiling fps :: Int
frameSet = map (\x -> (x # bg white, timediff)) frames
-- Compute width and height.
let shape = activeStart animAdjusted
w = width shape
h = height shape
aspect = w / h
imgHeight = 300
imgWidth = aspect * imgHeight
-- Write the image.
let filename = ".ihaskell-diagram.gif"
diagOpts = DiagramOpts {
_width = Just . ceiling $ imgWidth
, _height = Just . ceiling $ imgHeight
, _output = filename
}
gifOpts = GifOpts {
_dither = True
, _noLooping = False
, _loopRepeat = Nothing
}
mainRender (diagOpts, gifOpts) frameSet
-- Convert to ascii represented base64 encoding
imgData <- readFile $ fpFromString filename
return . unpack . base64 $ imgData
-- Rendering hint.
animation :: Animation Cairo R2 -> Animation Cairo R2
animation = id
...@@ -51,7 +51,7 @@ library ...@@ -51,7 +51,7 @@ library
exposed-modules: IHaskell.Display.Diagrams exposed-modules: IHaskell.Display.Diagrams
-- Modules included in this library but not exported. -- Modules included in this library but not exported.
-- other-modules: other-modules: IHaskell.Display.Diagrams.Animation
-- Language extensions. -- Language extensions.
default-extensions: DoAndIfThenElse default-extensions: DoAndIfThenElse
...@@ -66,7 +66,10 @@ library ...@@ -66,7 +66,10 @@ library
diagrams==1.2.*, diagrams==1.2.*,
diagrams-lib, diagrams-lib,
diagrams-cairo, diagrams-cairo,
ihaskell >= 0.5 ihaskell >= 0.5,
-- The active package, used to represent animations
active >= 0.1.0 && <0.1.1
-- Directories containing source files. -- Directories containing source files.
-- hs-source-dirs: -- hs-source-dirs:
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment