hack2: a Haskell Webserver Interface (V2)

[ bsd3, library, web ] [ Propose Tags ]

Hack2: a Haskell Webserver Interface (V2)


[Skip to Readme]

Modules

[Index]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 2011.6.10, 2011.6.19, 2011.6.20, 2012.1.19, 2014.11.17
Change log changelog.md
Dependencies base (>=3 && <99), bytestring, data-default (>=0.2) [details]
License BSD-3-Clause
Author Jinjing Wang
Maintainer Jinjing Wang <nfjinjing@gmail.com>
Category Web
Home page https://github.com/nfjinjing/hack2
Uploaded by JinjingWang at 2014-11-17T11:13:43Z
Distributions NixOS:2014.11.17
Reverse Dependencies 12 direct, 0 indirect [details]
Downloads 4289 total (12 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 hack2-2014.11.17

[back to package description]

Hack2: a Haskell Webserver Interface (V2)

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

Introduction

Idea

Separation of concerns:

  • hack2: interface spec
  • hack2-middleware: building blocks
  • hack2-handler: server backends

Design

type Application = Env -> IO Response

Demo

{-# LANGUAGE OverloadedStrings #-}

import Hack2
import Hack2.Contrib.Response (set_body_bytestring)
import Hack2.Handler.SnapServer

app :: Application
app = \env -> 
  return $ 
    Response 
      200 [ ("Content-Type", "text/plain") ] "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.
  • 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.
  • httpHeaders: 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, enumerator style.
  • hackErrors: The error stream.
  • hackHeaders: None standard http headers.

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, enumerator style.

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 hack2

install some hack helpers

cabal install hack2-contrib

pick a backend

cabal install hack2-handler-snap-server

Create a Hack app

put the following code in Main.hs

{-# LANGUAGE OverloadedStrings #-}

import Hack2
import Hack2.Contrib.Response (set_body_bytestring)
import Hack2.Handler.SnapServer
import Data.Default (def)

app :: Application
app = \env -> 
  return $ 
    set_body_bytestring "Hello World 2" $ 
      def { headers = [ ("Content-Type", "text/plain") ] }

main = run app

run

runghc Main.hs

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

Middleware

demo usage of middleware

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

{-# LANGUAGE OverloadedStrings #-}

import Hack2
import Hack2.Contrib.Response (set_body_bytestring)
import Hack2.Handler.SnapServer
import Data.Default (def)

import Data.ByteString.Char8 (pack)
import Hack2.Contrib.Utils (empty_app)
import Hack2.Contrib.Middleware.URLMap


say :: Application
say = \env -> return $ set_body_bytestring (pack $ show env) def

app :: Application
app = url_map [("/hello", say), ("/there", say)] empty_app

main = run app

create a middleware

inside Hack2.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 Hack2.Contrib.Middleware.Config (config) where

import Hack2

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

Use the middleware stack

From Hack2.Contrib.Utils:

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

Handlers

Once an application is written using Hack2, it should work on any web server that provides a Hack2 handler.

A handler should expose at least one function of type:

run :: Application -> IO ()

Upgrade

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

cabal install linked_lib --reinstall

Discuss:Web programming with Haskell