## Hack: a sexy Haskell Webserver Interface Hack is a brain-dead port of the brilliant Ruby [Rack](http://rack.rubyforge.org/) 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 our 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 ### demo usage of middle-ware 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 ### make a middle-ware inside Hack.hs: type MiddleWare = Application -> Application since Haskell has curry, middle-ware api can be of type Params -> Application -> Application just pass an applied middle-ware into a chain. finally the source code of SimpleRoute.hs: {-# LANGUAGE NoMonomorphismRestriction#-} {-# LANGUAGE QuasiQuotes #-} module Hack.SimpleRoute where import Hack import Hack.Utils import List (find) import Prelude hiding ((.), (^), (>)) import MPS type RoutePath = (String, Application) route :: [RoutePath] -> Application -> Application 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)