Readme for hack-2009.4.28

Hack: a sexy Haskell Webserver Interface

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

What does a Hack app look like

module Main where

import Hack
import Hack.Handler.Hyena

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

main = run hello

1 minute tutorial

update cabal

cabal update

install hyena

git clone git://github.com/tibbe/hyena.git
cd hyena
cabal install

install hack

cabal install hack

Create a Hack app

put the following code in src/Main.hs

module Main where

import Hack
import Hack.Handler.Hyena

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

main = run hello

run

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

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

Middleware

demo usage of middleware

module Main where

import Hack
import Hack.Utils
import Hack.SimpleRoute
import Hack.Handler.Hyena

import Data.Default
import MPS
import Prelude hiding ((.))

hello :: Application
hello = \env -> def {body = env.show} .return

app :: Application
app = route [("/hello", hello), ("", 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 SimpleRoute.hs:

{-# LANGUAGE QuasiQuotes #-}

module Hack.Contrib.SimpleRouter where

import Hack
import Hack.Utils

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

type RoutePath = (String, Application)

route :: [RoutePath] -> MiddleWare
route h app = \env ->
  let path             = env.path_info
      script           = env.script_name
      mod_env location = env 
        { script_name  = script ++ location
        , path_info    = 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

Rack provides a builder DSL, Hack just use a function. From Utils.hs:

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

Handlers

Just like Rack, once an application is written using Hack, it should work on any web server that provides a Hack handler. I'm only familiar with Kibro, so it became the first handler that's included.

The handler should expose only one function of type:

run :: Application -> IO ()

Spec

Hack spec = Rack spec :)

Please read The Rack interface specification.