orange juicetin πŸŠπŸ§ƒ

"functional art" - using Haskell to make generative art

Figured I'd do a writeup on another one of my projects that I did for the Recurse Center for Impossible Stuff Day! Where, aptly, we do something for the day we think is impossible.

...

me: "Mom can we have some generative art in Haskell"

turnage_art

mom: "son we have generative art at home"

*the generative art at home* (give it like 5 secs)

Achieving generation of this .gif took quite a while (and only with the help of some Recurse alum who are absolute Haskell legends (shoutout Alex Chen) walking me through state transformers *dies a little inside*). Yet, even this small project was incredibly educational and sparked a joy for coding in Haskell.

Once I had hit this steady-state where the remaining work to be done was to ~ make art ~ (as all the other pieces were in place and coded up), I figured I had learned plentifully enough to step away a bit for the time-being and do a write-up on it to solidify the learnings.

Would love to keep iterating and come back to this in the near future and post an update to this writeup. The next step is just testing out random cool algorithms1 to draw interesting patterns or randomize coloring and hues in new ways with the building blocks I coded up through this project. So many possibilities, not enough time!

How this got started (alternate subtitle: oooo pretty colors)

My prompt for Impossible Stuff Day during my Recurse Center batch: I thought it'd be impossible for me to like functional programming again (see: half of CIS120 my freshman spring being taught in OCaml; me, a greenhorn, bright-eyed-but-not-for-much-longer coder)

So, what better than trying to make some art with Haskell which you've never touched before to dive head-first into FP again!

I knew of Haskell because of CIS552 with Stephanie Weirich, which I've mentioned on this blog before for regretting not taking, but had never seen or written a single line of before.

After some clicks through the Creative Coding resources the day of, I stumbled upon this guide written in 2018 by Payton Turnage, and outside of this post and a similar one by someone named "Ben Kovach" (which you can't access the link to anymore either), there was not much else online about how one would go about this in Haskell. So, cool! A new problem to solve, and an interesting up-to-date walkthrough just waiting to be written.

Thus, I hope this can serve as a 2023 updated equivalent that carries the torch forward for anyone else curious about how Haskell can actually make some cool stuff in practice. Part of the struggle with Turnage's guide was dealing with deprecated Haskell dependencies and finding ways to carry it out in present day.

alright, some code

module Main (main) where

import Control.Monad.Reader
import Control.Monad.State
import qualified Data.Vector as V
import Graphics.Rendering.Cairo
import Linear.V2
import System.Random

data World = World
  { worldWidth :: Double,
    worldHeight :: Double,
    scaleFactor :: Double
  }

newtype Contour = Contour (V.Vector (V2 Double))

contourPath :: Contour -> Render ()
contourPath (Contour vertices) = sequence_ $ concat [initCmds, lines_, endCmds]
  where
    initCmds = [newPath, moveTo startX startY]
    lines_ = V.toList $ V.map (\(V2 xn yn) -> lineTo xn yn) $ V.tail vertices
    endCmds = [closePath]
    V2 startX startY = V.head vertices

type Generate a = StateT StdGen (Reader World) a

runGenerate :: World -> StdGen -> Generate a -> a
runGenerate world rng =
  flip runReader world . fmap fst . flip runStateT rng

bg :: Generate (Render ())
bg = do
  (World w h _) <- ask
  return $ do
    setSourceRGBA 0 0 0 1
    rectangle 0 0 w h
    fill

-- the animated state is our red value, but we can take this and switch up in any way that we'd like to!
draw :: State Double (Generate (Render ()))
draw = do
  red <- get
  if red >= 1
    then put 0
    else put $ red + 0.01
  return $ do
    (World w h _) <- ask
    green <- state $ uniformR (0, 1)
    blue <- state $ uniformR (0, 1)
    return $
      do
        setSourceRGBA red green blue 1
        contourPath $ Contour $ V.fromList ([V2 (w / 6) (h / 2), V2 (w / 6) (h / 4), V2 (5 * w / 6) (h / 4), V2 (5 * w / 6) (h / 2)])
        fill

sketch :: State Double (Generate (Render ()))
sketch = do
  draw_ <- draw
  return $ do
    rs <- sequence [bg, draw_]
    return $ sequence_ rs

animation :: Int -> State Double [Generate (Render ())]
animation frames = mapM (const $ sketch) [1 .. frames]

writeSketch :: World -> StdGen -> String -> Generate (Render ()) -> IO ()
writeSketch world rng filepath sketchs = do
  surface <- createImageSurface FormatARGB32 (round $ worldWidth world) (round $ worldHeight world)
  renderWith surface $ do
    scale (scaleFactor world) (scaleFactor world)
    runGenerate world rng sketchs
  surfaceWriteToPNG surface filepath

main :: IO ()
main = do
  let world = World 600 600 1
  let frames = 1
  let frameRenders = evalState (animation frames) 0
  rng <- initStdGen
  let filenames = map (\i -> show i ++ ".png") [1 .. frames]
  mapM_ (uncurry $ writeSketch world rng) $ zip filenames frameRenders

Whatever frames is equal to, it'll spit that number of images in the directory where your executable is, and from there you can use the convert command line tool from imagemagick to combine this into a .gif with convert -delay 10 -loop 0 {1..100}.png out.gif (it took me slightly too long to realize in Turnage's blog that he was talking about a command line util rather than another Haskell function...so I save you, the reader, the embarrassment of the same fate)

...

It's fairly short, yet it's still, I don't know, a lot? When I first started tackling this, it felt like I was learning how to walk again. Trying to read all the curried functions, obscure built-in functions, and interpreting the type signature of all the various packages, doing IO in Haskell, oh me oh my.

I'll share what I've learned, but in case you're here just for the meat of it and don't need much explaining, then the above is for you, source code available on my github as well. Also – if any packages or functions don't seem clear, Hoogle is your best friend, use it generously.

How do you draw in Haskell?

I/O in Haskell is incredibly hard. What is as easy as breathing air for imperative languages becomes this arduous abstraction in a pure2 language like Haskell where, by definition, it should have no side effects, so um, how do you draw? Much less print? Those are very much your run-of-the-mill side effects.

This is where the expansive topic of monads in Haskell comes in. The cairo binding for Haskell we're using relies heavily on this concept, so, it's important to understand.

However, there is a. lot. to. learn. about. monads. It's not an easy concept, hence everyone trying their hand at providing better intuition.

"Computation builder" isn't too bad of a description. Neither is "pattern for chaining operations". "Workflows" (as they're called in F#), "composable coding strategies". "Type-disciplined approach to pipes" is a little different flavor but I kinda like it. You should build your own way of viewing these too, and use whatever makes it make the most sense.

It's through this abstraction that we can accomplish I/O through the IO Monad. There are other more common monads that you'll see in Haskell that fit this idea of being a "workflow", such as Maybe (rescues you from having to constantly write null checks) or List (you need a basic collection of items with the same type and with predictable behavior/performance).

There is a lot of syntax that comes along with monads, such as monadic binds (>>= or >>), do notation, the latter of which you'll see plenty of throughout these snippets.

With this concept of monads in hand, the cairo library relies on the Render monad to be the context for all drawings. If you look at the background that we create with bg:

bg :: Generate (Render ())
bg = do
  (World w h _) <- ask
  return $ do
    setSourceRGBA 0 0 0 1
    rectangle 0 0 w h
    fill

The Generate is just a type that we create to serve as a wrapper to incorporate state (State) and a shared environment (Reader which reads in the World type that we defined to be our environment):

data World = World
  { worldWidth :: Double,
    worldHeight :: Double,
    scaleFactor :: Double
  }
...
...
type Generate a = StateT StdGen (Reader World) a

State is hard in Haskell – again, in a pure language, we don't really have mutable variables that we'd normally have in imperative programming, so doing things "statefully" in our computations looks entirely different. And the reason that we need stateful computation here is our introduction of randomness into our code through StdGen to randomly generate starting colors for our .gif (and later down the line, our drawings and patterns!), so this makes our job a bit tougher than just drawing basic shapes in Cairo.

Yet, it's not impossible! This is where our State monad comes in, and boy oh boy is this another big topic that forms the foundation for tons of future Haskell code. The lecture that I linked to is, again, Stephanie Weirich's writeup from her CIS552 course at Penn, and I would highly recommend reading through it as a way to a) keep building one's understanding of monads and b) tackle the difficult topic of the State monad relatively intuitively and in a slow, built-up fashion.

...

Midway through writing this, combined with some writing fatigue, I realized that to continue this blog post (sans further updates on finished artwork progress or explaining a few other steps I took) would make this writeup a mindless, overly long and complicated walkthrough of cool Haskell features that could easily just be broken up into smaller, more digestible blog posts in the future (just like in clean code!). It should say enough that for one concept like State to be covered, whole other writeups exist at length, so to try and tackle it fully in my own singular writeup combined with other topics would be ambitious of me.

For that reason, I'll be cutting the writeup short here. I'm happy with this writeup remaining as an introductory Haskell post with my code and its original motivation on display (again, if anything is unclear, Hoogle it!), with monads and certain foundational concepts painted in broad strokes to hopefully give you, the reader, a taste for why Haskell can be fun to wrestle around with to try and accomplish something! It tests the way one thinks in the best of ways, and makes every successful GHC compilation a small but momentous victory.

Go forth and explore!


  1. of which there are soo many. There's quite the community out there dedicated to generative art, r/generative being a big one, the whole field being a much more active community than I ever anticipated

  2. this Stack Overflow post contains some of the discourse concerning what it means to be a "pure" language, though there's not one absolutely-agreed-upon answer. The general ideas holds however.