Readme for hack-2009.7.15

Hack: a Haskell Webserver Interface

Hack is a brain-dead port of the brilliant Ruby Rack webserver interface.

Introduction

Idea

Separation of concerns:

Design

type Application = Env -> IO Response

Demo

import Hack
import Hack.Handler.Happstack
import Data.ByteString.Lazy.Char8 (pack)

app :: Application
app = \env -> return $
  Response 200 [ ("Content-Type", "text/plain") ] (pack "Hello World")

main = run app

Spec

The Environment

The Response

Properties

1 minute tutorial

update cabal

cabal update

install hack

cabal install hack

pick a backend

cabal install hack-handler-happstack

Create a Hack app

put the following code in src/Main.hs

import Hack
import Hack.Handler.Happstack
import Data.ByteString.Lazy.Char8 (pack)

app :: Application
app = \env -> return $ Response 
    { status  = 200
    , headers = [ ("Content-Type", "text/plain") ]
    , body    = pack "Hello World"
    }

main = run app

run

ghc --make -O2 Main.hs
./Main

It should be running on http://127.0.0.1:3000 now.

Middleware

demo usage of middleware

install hack-contrib:

cabal install happy
cabal install hack-contrib

put the following in Main.hs. This code uses the URLMap middleware to route both /hello and /there to the hello application.

import Hack
import Hack.Handler.Happstack
import Hack.Contrib.Utils
import Hack.Contrib.Middleware.URLMap
import Data.ByteString.Lazy.Char8 (pack)
import Data.Default

hello :: Application
hello = \env -> return $ def {body = pack $ show env, status = 200}

app :: Application
app = url_map [("/hello", hello), ("/there", hello)] empty_app

main = run app

create a middleware

inside Hack.hs:

type Middleware = Application -> Application

since Haskell has curry, middleware api can be of type

Anything -> Application -> Application

just pass an applied middleware into a chain.

finally the source code of URLMap.hs:

module Hack.Contrib.Middleware.URLMap (url_map) where

import Hack
import Hack.Contrib.Utils

import MPSUTF8
import Prelude hiding ((.), (^), (>))
import List (find, isPrefixOf)

type RoutePath = (String, Application)

url_map :: [RoutePath] -> Middleware
url_map h app = \env ->
  let path             = env.path_info
      script           = env.script_name
      mod_env location = env 
        { scriptName  = script ++ location
        , pathInfo    = path.drop (location.length)
        }
  in
  case h.find (fst > (`isPrefixOf` path) ) of
    Nothing -> app env
    Just (location, app') -> app' (mod_env location)

Use the middleware stack

From Hack.Contrib.Utils:

-- usage: app.use [content_type, cache]
use :: [Middleware] -> Middleware
use = reduce (<<<)

Handlers

Once an application is written using Hack, it should work on any web server that provides a Hack handler.

The handler should expose only one function of type:

run :: Application -> IO ()

Upgrade

With every new hack release, any library links hack should be recompiled, usually it's simply:

cabal install linked_lib --reinstall

Discuss

Wiki