hack: a Haskell Webserver Interface

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

Hack: a Haskell 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 (>=3 && <5), bytestring, data-default (>=0.2) [details]
License BSD-3-Clause
Author Wang, Jinjing
Maintainer Wang, Jinjing <e .nfjinjing@gmail.com>
Category Web
Home page http://github.com/nfjinjing/hack/tree/master
Uploaded by JinjingWang at 2009-07-15T16:13:01Z
Distributions NixOS:2012.2.6
Reverse Dependencies 28 direct, 3 indirect [details]
Downloads 12093 total (42 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.7.15

[back to package description]

Hack: a Haskell Webserver Interface

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

Introduction

Idea

Separation of concerns:

  • hack: the spec
  • hack-middleware: building blocks
  • hack-handler: back-ends

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

  • requestMethod: The HTTP request method, e.g. GET, POST.
  • scriptName: The initial portion of the request URL‘s “path” that corresponds to the application object, so that the application knows its virtual “location”. This may be an empty string, if the application corresponds to the “root” of the server.
  • pathInfo: The remainder of the request URL‘s “path”, designating the virtual “location” of the request‘s target within the application. This may be an empty string, if the request URL targets the application root and does not have a trailing slash. This value may be percent-encoded when I originating from a URL.
  • queryString: The portion of the request URL that follows the ?, if any. May be empty, but is always required!
  • serverName, serverPort: When combined with scriptName and pathInfo, these variables can be used to complete the URL. Note, however, that Host in http field, if present, should be used in preference to serverName for reconstructing the request URL. serverName and serverPort can never be empty, and so are always required.
  • http: Variables corresponding to the client-supplied HTTP request headers (e.g. "Accept"). The presence or absence of these variables should correspond with the presence or absence of the appropriate HTTP header in the request.
  • hackVersion: The list of Int, representing this version of Hack
  • hackUrlScheme: HTTP or HTTPS, depending on the request URL.
  • hackInput: The body of the request.
  • hackErrors: The error stream.
  • hackHeaders: None http headers, intended to be used by handlers and middleware.

The Response

  • status: This is an HTTP status. It must be greater than or equal to 100.
  • headers: The header must not contain a Status key, contain keys with : or newlines in their name, contain keys names that end in - or _, but only contain keys that consist of letters, digits, _ or - and start with a letter. The values of the header must be Strings, consisting of lines (for multiple header values) separated by “\n”. The lines must not contain characters below 037.
  • body: The body of the response.

Properties

  • The scriptName, if non-empty, must start with /
  • The pathInfo, if non-empty, must start with /
  • One of scriptName or pathInfo must be set. pathInfo should be / if scriptName is empty. scriptName never should be /, but instead be empty.

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