Skip to content
October 5, 2010 / cdsmith

Using Heist and Happstack

In the course of playing around with some of the newer Haskell web application stuff recently, I found that I really like the combination of Happstack and Heist.  However, there are a few challenges in getting the two to play together well, so I thought I’d write up a description of how to do it.

Step 1: Getting the dependencies right

When creating your cabal file, you’ll generally need at least the following packages:

  • base (of course)
  • happstack-server, for the Happstack bits
  • heist, for the Heist bits
  • bytestring, since it’s used extensively with Heist
  • mtl, which is used in Happstack
  • monads-fd, which is used in Heist

Those last two make for a rather unhappy combination, and are the subject of the next step.

Step 2: Making mtl and monads-fd play nicely

This took some figuring out.  Basically, a good bit of Heist uses the MonadIO class from monads-fd.  At the same time, Happstack uses the MonadIO class from mtl.  Left to their own devices, this will lead to a lot of errors that ServerPartT IO is not an instance of MonadIO.  Of course it is… just not that MonadIO.

Here’s the code I eventually wrote to fix it.  You’ll need a number of GHC extensions to do this.

{-# LANGUAGE PackageImports       #-}
{-# LANGUAGE FlexibleInstances    #-}

import "mtl" Control.Monad.Trans

{-
    Needed because Heist uses transformers rather than the old mtl package.
-}
import qualified "monads-fd" Control.Monad.Trans as TRA
instance TRA.MonadIO (ServerPartT IO) where liftIO = liftIO

The language extension PackageImports allows us to import modules from a specific package.  In general, it’s a bad idea if you can avoid it as it can lead to fragile code… but since here we are facing the challenge of making two packages work together, there’s not another choice.  We use this extension to import both the mtl and monads-fd versions of the MonadIO type class.  The second language extension, FlexibleInstances, relaxes some of the Haskell98 rules regarding what kinds of instances are allowed.  It is needed for the instance declaration on the last line there, and it’s pretty harmless.

Once we’ve got both versions of MonadIO and its member, liftIO, imported properly, we simply write an instance declaration making ServerPartT IO an instance of the monads-fd version of MonadIO (copying the actual behavior straight from the mtl version).  Voila, problem solved.

Step 3: Porting the glue code

If you’ve worked through the Snap tutorial, you know that you can start a new Snap project by typing ‘snap init’ at the command line, and the command writes a bit of code for you.   That code includes a module called “Glue” that’s largely about making Snap and Heist work together.  Well, we’ll need the same code for Happstack, and have no automated command to write it for us.  Not to worry, though, it’s a piece of cake to port it over, and you can tweak it as you go.

Here’s the very simple application I ended up with that uses Heist in Happstack.  This is the full source code; it assumes that underneath the current working directory when the application is run, there’s a directory called “web” containing your templates, and a subdirectory of that called “web/static” containing your static files.

{-# LANGUAGE OverloadedStrings    #-}
{-# LANGUAGE PackageImports       #-}
{-# LANGUAGE FlexibleInstances    #-}

module Main where

import Control.Monad (msum, mzero)
import Happstack.Server
import Happstack.Server.HTTP.FileServe
import Text.Templating.Heist
import Text.Templating.Heist.TemplateDirectory

import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy  as L

import "mtl" Control.Monad.Trans

{-
    Needed because Heist uses transformers rather than the old mtl package.
-}
import qualified "monads-fd" Control.Monad.Trans as TRA
instance TRA.MonadIO (ServerPartT IO) where liftIO = liftIO

main :: IO ()
main = do
    td <- newTemplateDirectory' "web" emptyTemplateState
    simpleHTTP nullConf $ msum [
        dir "static" $ fileServe [] "web/static",
        templateServe td,
        dir "reload" $ nullDir >> templateReloader td,
        ]

templateReloader td = do
    e <- reloadTemplateDirectory td
    return $ toResponseBS "text/plain; charset=utf-8" $
        L.fromChunks [either B.pack (const "Templates loaded successfully.") e]

templateServe td = msum [
    nullDir >> render td "index",
    withRequest (return . rqUri) >>= render td . B.pack
    ]

render td template = do
    ts    <- getDirectoryTS td
    bytes <- renderTemplate ts template
    flip (maybe mzero) bytes $ \x -> do
        return (toResponseBS "text/html; charset=utf-8" (L.fromChunks [x]))

And that’s it! You have a working Happstack application using Heist as a template engine.

5 Comments

Leave a Comment
  1. Jeremy Shaw / Oct 6 2010 1:21 pm

    Nice!

    I have been hoping to get official support for heist into happstack since heist does provide a new style of templates that seems useful.

    What do you think would be require for official support ? A ToMessage instance for responses would be nice. It seems like the biggest annoyance is the mtl vs monads-fd support.

    Happstack is by no means committed to sticking with mtl. But, I wonder if it is too early for happstack to make the switch? Your workaround seems reasonable in the meantime though..

  2. cdsmith / Oct 6 2010 1:33 pm

    I honestly don’t think much else is needed. It’s a testament to both packages, I think, that they can be made to work together in around a dozen lines of code, and no added complexity is necessary except for the well-known mtl/transformers issue. By contrast, Michael Snoyman’s persistent package looks tempting as well, but I’ve avoided it so far because the list of dependencies includes hamlet and web-routes-quasi, and I anticipate some hoop-jumping there.

    I’m working on a somewhat involved web site now, though, that I intend to write in Happstack and Heist, so I’ll be in a better position to answer that question in about two to three weeks.

  3. gracjanpolak / Oct 20 2010 11:47 pm

    To make the instance a bit more general you can use:

    import qualified “monads-fd” Control.Monad.Trans as TRA
    instance (MonadIO m) => TRA.MonadIO (ServerPartT m)
    where liftIO = liftIO

  4. Jeremy Shaw / Nov 7 2010 9:59 pm

    Hello,

    I just uploaded a new stable happstack, and patched the development version of happstack to use mtl-2:

    http://groups.google.com/group/happs/browse_thread/thread/9f1e3d4d4e6061c3

    My understanding is that mtl-2 is what used to be called monads-fd, and monads-fd is now a dummy package that imports mtl-2.

    So, I think that means you should be able to use heist with happstack without having to do any MonadIO hackery provided you rebuild happstack against mtl-2 ?

    – jeremy

  5. Jeremy Shaw / Nov 15 2010 3:56 pm

    I packaged this up and put it on hackage. (I put your name in the copyright).

    http://happstack.blogspot.com/2010/11/ann-happstack-heist-now-in-darcs.html

    Thanks!

Leave a comment