hack: a sexy Haskell Webserver Interface

[ bsd3, deprecated, library, web ] [ Propose Tags ]
Deprecated in favor of hack2
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 ansi-wl-pprint, base, base64-string, bytestring, cgi, containers, data-default (>=0.2), directory, filepath, haskell98, kibro (>=0.4.3), mps (>=2009.4.21), network, old-locale, old-time, template, time, unix, zlib [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-04-24T19:48:57Z
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.4.25

[back to package description]

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.Kibro

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

main = run hello

1 minute tutorial

Install Hack

cabal install hack

Install Kibro (the only handler at the moment)

cabal install kibro

Install lighttpd 1.4.19 (used by kibro)

wget http://www.lighttpd.net/download/lighttpd-1.4.19.tar.gz
tar zxfv lighttpd-1.4.19.tar.gz
cd lighttpd-1.4.19
./configure --prefix=$HOME
make
make install

Create a new Kibro project

kibro new hello-world

Test if Kibro works

cd hello-world
kibro start

Create a Hack app

put the following code in src/Main.hs

module Main where

import Hack
import Hack.Handler.Kibro

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

main = run hello

restart kibro

kibro restart

Middleware

demo usage of middleware

module Main where

import Hack
import Hack.Utils
import Hack.SimpleRoute
import Hack.Handler.Kibro

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 List (find)
import Prelude hiding ((.), (^), (>))
import MPS

type RoutePath = (String, Application)

route :: [RoutePath] -> MiddleWare
route h _ = \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 > flip starts_with path) of
    Nothing -> not_found [$here|Not Found: #{path}|]
    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.