hack: a sexy Haskell Webserver Interface

[ bsd3, deprecated, library, web ] [ Propose Tags ]
Deprecated in favor of hack2

Hack: a sexy Haskell Webserver Interface. Hack is a brain-dead port of the brilliant Ruby Rack http://rack.rubyforge.org/ webserver interface.


[Skip to Readme]

Modules

[Index]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 2009.4.20, 2009.4.21, 2009.4.22, 2009.4.23, 2009.4.25, 2009.4.26, 2009.4.27, 2009.4.28, 2009.4.29, 2009.4.30, 2009.4.51, 2009.4.52, 2009.5.19, 2009.7.15, 2009.10.30, 2012.2.6
Change log changelog.md
Dependencies base, bytestring, data-default (>=0.2) [details]
License LicenseRef-GPL
Author Wang, Jinjing
Maintainer Wang, Jinjing <nfjinjing@gmail.com>
Category Web
Home page http://github.com/nfjinjing/hack/tree/master
Uploaded by JinjingWang at 2009-05-19T01:38:49Z
Distributions NixOS:2012.2.6
Reverse Dependencies 28 direct, 3 indirect [details]
Downloads 12032 total (49 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for hack-2009.5.19

[back to package description]

Hack: a sexy Haskell Webserver Interface

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

Hack is made of 3 parts:

  • hack: the spec
  • hack-contrib: middleware
  • hack-handler: drivers

The spec should be as stable as possible, hack-contrib is about middleware and tools, and hack-handler provides server connectivity.

Hack explained in one line

type Application = Env -> IO Response

What does a Hack app look like

module Main where

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

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

module Main where

import Hack
import Hack.Handler.Happstack

app :: Application
app = \env -> return $ Response 
    { status  = 200
    , headers = [ ("Content-Type", "text/plain") ]
    , body    = "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. The code uses the SimpleRouter middleware to route both /hello and /there to the hello application.

module Main where

import Hack
import Hack.Handler.Happstack
import Hack.Contrib.Utils
import Hack.Contrib.Middleware.SimpleRouter

import Data.Default

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

app :: Application
app = route [("/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 SimpleRouter.hs:

module Hack.Contrib.Middleware.SimpleRouter where

import Hack
import Hack.Contrib.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 Contrib.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

See hack doc

Resources

Reference