osa1 github gitlab twitter cv rss

Combining digestive-functors and heist with Snap (continued from last tutorial)

January 4, 2014 - Tagged as: haskell, en.

Here’s an high-level overview of last post:

In this post, I’m going to add some functionalities from Snap to serve HTML pages from a server and handle routing and POST request processing. Our forms will be served at root and when we submit our form, we will be informed whether user creating was successful or what was the problem.

Recommended way fo starting a Snap applcation is by using snap init command. It creates a cabal project structure with Application.hs, Site.hs and Main.hs. According to Snap docs, we only rarely need to touch Main.hs. The other two files are used to create a new Snaplet, and only function we need to provide to Main module is app :: SnapletInit App App for some App type.

In this post I’m assuming you created a Snap project using snap init command and have Main.hs file. You don’t need Application.hs file and in this post we’ll be writing Site.hs file.

Required for some Snap features

{-# LANGUAGE TemplateHaskell     #-}
module Tut2 (app) where
import           Control.Applicative        (Applicative (..), (<$>))
import           Data.Maybe                 (isJust)
import qualified Data.Text                  as T

from `digestive-functors’ package

import           Text.Digestive

from `digestive-functors-heist’ package

import           Text.Digestive.Heist       (bindDigestiveSplices)

from lens package, required for Snaplets

import           Control.Lens
import           Snap.Snaplet
import           Snap.Snaplet.Heist

from bytestring package, required for some Snap functions

import qualified Data.ByteString            as B

from digestive-functors-snap package, required for form rendering, we had handled that using getForm and postForm from Text.Digestive.Heist before.

import           Text.Digestive.Snap        (runForm)

snap init creates a project with only this code in Application.hs:

data App = App
    { _heist :: Snaplet (Heist App)
    }

makeLenses ''App

instance HasHeist App where
    heistLens = subSnaplet heist

In this post I’m copying this code to Site.hs and removing Application.hs file. Here, I only changed the definition of App. Since our application is minimal, we only need Heist Snaplet nested in our App. When we need other functionalities in the future(like database access), we will extend this definition for new Snaplets.

app :: SnapletInit App App

First type parameter of SnapletInit is for type of parent Snaplet. In our case, we don’t have a parent Snaplet but I guess this is what you do in that case. Second type is currently initialized Snaplet’s type.

app = makeSnaplet "app" "An snaplet example application" Nothing $ do

Type of makeSnaplet is really helpful to understand what’s going on at the level of types:

makeSnaplet
  :: T.Text                  -- ^ Default ID of the Snaplet, I have no idea where is this used.
     -> T.Text               -- ^ Description of the Snaplet, again, no idea where is this used.
     -> Maybe (IO FilePath)  -- ^ Root folder for Snaplet's filesystem content. In case your Snaplet works on files.
     -> Initializer b v v    -- ^ Initializer for the Snaplet.
     -> SnapletInit b v      -- ^ SnapletInit is an opaque type for internal use. It's needed for embedding our snaplet to other snaplets.

We’re nesting Heist snaplet provided by Snap.Snaplet.Heist from snap package

   h <- nestSnaplet "" heist $ heistInit "templates"

self explanatory, see definition below

   addRoutes routes
   return $ App h
 where
   routes :: [(B.ByteString, Handler App App ())]

routes are how we handle requests. Handler type takes 3 arguments, but I’m yet to figure out what do these arguments mean. I guess these are same as arguments in SnapletInit type, except the last one is for return values of Handler functions.

   routes = [ ("/", mainHandler) ]

mainHandler is our handler function. Thanks to runForm function provided by Text.Digestive.Snap, we don’t need to anything because it handles POST/GET requests and renders form templates depending on request data. heistLocal function is provided by Snap.Snaplet.Heist and runs a handler action(in our case, this is render "user_form") on a modified Heist state. We’re modifying Heist state by binding our user form splices using bindDigestiveSplices as we did in previous post.

mainHandler :: Handler App App ()
mainHandler = do
    (formView, maybeUser) <- runForm "userform" userForm
    heistLocal (bindDigestiveSplices formView) $ render "user_form"

This is some code from previous post.

data User = User
    { uUsername :: T.Text
    , uEmail    :: T.Text
    , uKarma    :: Int
    } deriving (Show)


userForm :: Monad m => Form T.Text m User
userForm = User
    <$> "username"  .: text Nothing
    <*> "email"     .: check "invalid email" validateEmail (text Nothing)
    <*> pure 0
  where
    validateEmail :: T.Text -> Bool
    validateEmail = isJust . T.find (== '@')

As last thing, we need to copy our template file to snaplets/heist/templates. This is because of the way Snap handles Snaplets. I think what happens is for every Snaplet nested in a Snap application, Snap creates a folder in snaplets/snaplet_name and later when that Snaplet requires some filesystem operations, all paths are handled relative to this directory.

After that, if you compile and run the application, you can see our form at http://0.0.0.0:8000 and you can test error messages.