Readme for hack2-2011.6.10

Hack2: a Haskell Webserver Interface (V2)

Hack2 is a port of Ruby's Rack webserver interface.

Version

2011.6.10

Introduction

Idea

Separation of concerns:

Design

type Application = Env -> IO Response

Demo

{-# LANGUAGE OverloadedStrings #-}

import Hack2

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

Spec

The Environment

The Response

Properties

1 minute tutorial

update cabal

cabal update

install hack

cabal install hack2

pick a backend

cabal install hack2-handler-happstack

Create a Hack app

put the following code in Main.hs

{-# LANGUAGE OverloadedStrings #-}

import Hack2
import Hack2.Handler.HappstackServer

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

main = run app

run

runghc Main.hs

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

Middleware

(below is waiting to be finished)

demo usage of middleware

install hack-contrib:

cabal install hack-contrib

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

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

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

app :: Application
app = url_map [("/hello", say), ("/there", say)] 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 Config.hs:

module Hack.Contrib.Middleware.Config (config) where

import Hack

config :: (Env -> Env) -> Middleware
config alter app = \env -> app (alter env)

Use the middleware stack

From Hack.Contrib.Utils:

-- usage: use [content_type, cache] app
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.

A handler should expose at least one function of type:

run :: Application -> IO ()

Upgrade

With every new release, any library links to hack should be recompiled against the new version, usually as simple as:

cabal install linked_lib --reinstall

Discuss:Web programming with Haskell