New Haskell diagrams library

For the past week or so I’ve been working on an embedded domain-specific language for rendering simple diagrams with Haskell, and I’m excited to actually release version 0.1 today! You can now find it on Hackage. Version 0.1 is still fairly primitive, and there are a bunch more planned features, but you can already use it to create some pretty pictures. Here are a few examples.

We’ll start with a basic ‘hello world’ type diagram: a two-by-five rectangle, no frills:

module Main where
import Graphics.Rendering.Diagrams

main = renderToPng "hello.png" 100 100 (rect 2 5)

OK, not too exciting, but at least it was easy. Here’s another silly example that shows off a few more available features:

module Main where
import Graphics.Rendering.Diagrams

shapes :: Diagram
shapes = hcat [ fc blue $ circle 10
              , (fc goldenrod . lc green . lw 3 $ poly 5 10)
                ## (fc red . rotate (1/10) $ rect 4 4)
              , fc grey . lw 0 . scaleY 3 $ circle 5
              ]

main = renderToPng "shapes.png" 200 200 shapes

Hopefully, this example is fairly self-explanatory. We can alter the appearance of diagrams by applying functions to them like fc (fill color), lc (line color), lw (line width), rotate, and scaleY. We can superimpose two diagrams with ##. And we can lay out a list of diagrams horizontally with hcat. There are many other combinators along similar lines, with various options for distributing and aligning subdiagrams.

Now for a couple cooler examples. How about a Sierpinski triangle?

module Main where

import Graphics.Rendering.Diagrams
import Graphics.Rendering.Diagrams.Types

import qualified Graphics.Rendering.Cairo as C
import Graphics.Rendering.Diagrams.Shapes (draw)

data EqTri = EqTri  deriving Show
instance ShapeClass EqTri where
  shapeSize _   = (2, sqrt 3)
  renderShape _ = do
    c $ C.moveTo 1 s
    c $ C.lineTo 0 (-s)
    c $ C.lineTo (-1) s
    c $ C.closePath
    draw
   where s = sqrt 3 / 2

sierpinski :: Int -> Diagram
sierpinski 0 = fc black $ lw 0 $
               shape EqTri
sierpinski n = vcatA hcenter [         s
                             ,      s <> s]
  where s = sierpinski (n-1)

main = renderToPng "sierpinski.png" 300 300 (sierpinski 6)

This example illustrates a couple key points. One is that the library is easy to extend with new shapes. The built-in poly function is too general to provide a nice equilateral triangle for use in making a sierpinski triangle (its bounding box is too large, which would lead to ugly spaces in the diagram), so we can define our own shape just by making an instance of ShapeClass, and using the Cairo library to draw a path defining the shape. This is probably not the best way to accomplish this particular task — future versions of the diagrams library will include easier ways — but it’s a nice example of how easy it is to extend the basic library functionality.

The other key point is how much power we get for free from the fact that this is an embedded DSL. We can use the full power of Haskell to define a recursive function for computing sierpinski triangle diagrams.

For a final example, here are some nice Ford circles:

module Main where

import Graphics.Rendering.Diagrams

import Data.Ratio
import System.Random

(<+>) :: Rational -> Rational -> Rational
r1 <+> r2 = (numerator r1 + numerator r2) % (denominator r1 + denominator r2)

farey :: Integer -> [Rational]
farey 0 = [0%1, 1%1]
farey n = insertMediants (farey (n-1))

insertMediants :: [Rational] -> [Rational]
insertMediants [] = []
insertMediants [x] = [x]
insertMediants (x:y:zs) = x : (x <+> y) : insertMediants (y:zs)

fordCircles :: Integer -> [Diagram]
fordCircles n = map toCircle (filter ((<= n) . denominator) $ farey n)

toCircle r = translateX r' $
             circle (1 / (2 * d'^2))
  where r' = fromRational r
        d' = fromIntegral (denominator r)

dia :: [Color] -> Diagram
dia colors = view (0,-1/2) (1,0) $
             unionA hcenter bottom $
             zipWith fc colors (fordCircles 20)

randomColors :: [Double] -> [Color]
randomColors (r:g:b:ds) = rgb r g b : randomColors ds

main :: IO ()
main = do
  g <- newStdGen
  let rs = randoms g
  renderToPng "ford.png" 400 205 (dia $ randomColors rs)

Plans for future versions of the library include:

  • text objects
  • settable backgrounds and better support for transparency
  • support for line join style and dashing
  • more primitive shapes: special triangles, ellipses, bezier curves, lines, arrows…
  • more layouts: grid, tree, circle…
  • constraint-based placement of objects, e.g. to connect diagrams with arrows
  • more output modes: ps, svg, pdf
  • and more!

If this looks interesting to you, I hope you’ll download the library and play around with it! (Note that it does require the Cairo bindings, which are packaged as part of gtk2hs, which is unfortunately not yet Cabalized.) I would be happy to receive any and all feedback, including feature suggestions, bug reports, and pretty pictures. If you’re interested in contributing code, the darcs repository can be found at http://code.haskell.org/diagrams/.

Enjoy!

About Brent

Associate Professor of Computer Science at Hendrix College. Functional programmer, mathematician, teacher, pianist, follower of Jesus.
This entry was posted in haskell, projects and tagged , , , , , , . Bookmark the permalink.

9 Responses to New Haskell diagrams library

  1. jfredett says:

    Sweet, will it be able to do animation? It’d be nice to be able to hack up some cheap data visualization when I’m working on physics simulations or something…

  2. Brent says:

    jfredett: sure. You could already do animation with it now, with not too much trouble. Since it’s an embedded DSL it’s a piece of cake to have a function which takes some sort of frame index as input and outputs an appropriate diagram, then map this function over a list of frame indices, and map renderToPng over the resulting list of diagrams. Then use some external tool to put the PNG files together into an animation. I can probably include some built-in support for this kind of thing in future versions, too.

  3. your graphics are spatially continuous. go for temporally continuous animation. no pixels, no frame numbers. then you’ll get the same resolution-independence and scalability in time as you get in space. for example, check out FRP.

  4. by the way, sweet library and examples!

  5. Brent says:

    Conal: thanks! And good idea re: temporally continuous animation. If I add some built-in support for animation (I’ll probably add a bit, although that’s not really the main goal of the library) I’ll try to take that approach.

  6. Dougal says:

    That sounds pretty neat… I can already think of something I’d like to do with it! Keep us updated if you’re going to make a repository available. I’m keen to get a look at it (and contribute if I can).

  7. Brent says:

    Dougal: great! I will definitely put up a repository, just waiting for an admin to create a directory for me on code.haskell.org. I’ll be sure to let you (and anyone else who’s interested) know.

  8. Pingback: Looking Out To Sea » Lord of the Flies as a window onto monadic IO

  9. Pingback: Looking Out To Sea » It’s like a comic for people who can’t draw

Leave a reply to jfredett Cancel reply

This site uses Akismet to reduce spam. Learn how your comment data is processed.