Hack

I am investing alternative ways of developing web apps. I've looked at PLT-Scheme which was a nice framework to develop in, but missing a nice database abstraction layer like fe. SQLAlchemy in python. And in retrospect my conclusion on Scheme is that I find it a little verbose, expecially compared to Haskell. I like succintness, it gives a lot of power as descibed by Paul Graham in Succintness is Power.

The quantity of meaning compressed into a small space by algebraic signs, is another circumstance that facilitates the reasonings we are accustomed to carry on by their aid.
Charles Babbage, quoted in Iverson's Turing Award Lecture

Wat is hack?

Hack is inspired from ruby's Rack, WSGI Python, Ring in Clojure. In abstract terms Env -> Reponse. Hack is the Rack protocol implemented in Haskell. I stumbled upon hack while examining Loli developed by the same author Nfjinjing.

MPS notiation

Nfjinjing likes to turn the normal Haskell syntax around and uses his own util library MPS (Message passing style) which turns the order of normal Haskell syntax around making it look like a OO language (to relieve his already punished OO brain).

See MPS for the syntax implmeneted. I have collected the important code snippets from MPS:

  {-# INLINE (.) #-}
  (.) :: a -> (a -> b) -> b
  a . f = f a
  infixl 9 .

  (>) :: (Category cat) => cat a b -> cat b c -> cat a c
  (>) = (>>>)
  infixl 8 >

  (<) :: (Category cat) => cat b c -> cat a b -> cat a c
  (<) = (<<<)
  infixr 8 <

  (^) :: (Functor f) => f a -> (a -> b) -> f b
  (^) = flip fmap
  infixl 8 ^

Nothing really complicated but makes the code more succint. Which can be a good thing ;)

How does hack work?

type Application = Env -> IO Response

type Middleware = Application -> Application

In essence it is a mimimal representation of what every webserver does. It gets a Request which build an environment to which a Repsonse gets formed.

To see the typedefinitions for Env and response look below. It comes back in Loli. It's a nice and minimal implementation consisting of one file Hacks.hs. Very minimal. Nice..

Hack-contrib

Contains functions to interact with the hack specification. The hack datatypes:

Hack-contrib middleware, or how to extend Hack

Just as in Clojures Ring, and Ruby's rack, middleware consists of a function which wraps another function which does something with either dispatching or the environment or the response. It is a very clean seperation of concerns which enables composition of components in a very flexible decoupled way.

Take as example the regexp router, which is an example of a middleware compononent:

  type RoutePath = (String, Application)

  type Middleware = Application -> Application

  type Application = Env -> IO Response

  regexp_router :: [RoutePath] -> Middleware
  regexp_router h app = \env ->
    let path = env.path_info
    in
    case h.find (fst > flip match path > isJust) of
      Nothing -> app env
      Just (_, found_app) -> found_app env

Returns a lambda which receives environment. Acts upon this evironment and runs the found_app if a route matches or dispatches to then next in middleware pipeline, ending utlimately in returning an IO Repsonse at the en of the chain.

Below another example of a middleware, this is static file serving.

  file :: Maybe String -> Middleware
  file root _ = \env -> do
    let path = env.path_info .unescape_uri
    if ".." `isInfixOf` path
      then forbidden
      else path.serve root

Hack-contrib provides at this moment (Tue May 25 ) the following Middlewares:

Loli

What is loli?

Minimal Web DSL written on top of hack. It's a very succint dsl language to define web apps. As 'webpy' in python.

Example app

main ::  IO ()
main = run 3000 . loli - do
     get "/bench" - do
        name <- ask ^ params ^ lookup "name" ^ fromMaybe "nobody"
        html ("<h1>" ++ name ++ "</h1>")

     get "/" (text "loli power")

Lets dive in ..

Looks pretty efficient, what exactly happens here? To understand let's look at the used types.

run ::  Hack.Handler.SimpleServer.Port -> Hack.Application -> IO ()

loli ::  Network.Loli.Type.Unit -> Hack.Application

-- Network.Loli.Type.Unit    
type UnitT a = State Loli a
type Unit    = UnitT ()

data Loli = Loli
  {
    current_router  :: Router
  , routes          :: [RouteConfig]
  , middlewares     :: [Middleware]
  , mimes           :: Assoc
  }

So in abstracto Loli dsl functions like get. Define an Appunit.

get :: String -> Network.Loli.Type.AppUnit -> Network.Loli.Type.Unit

Appunit is defined as:

type AppReader    = Env
type AppState     = Response
type AppUnitT     = ReaderT AppReader (StateT AppState IO)
type AppUnit      = AppUnitT ()

And could be seen as the AppUnit which will be run on a Hack Application

AppUnitT is a double MonadTransformer

Env and Response are defined inside the Hack libraries and defined below.

data Env = Env 
  {  requestMethod :: RequestMethod            -- ^ HTTP request method ....
  ,  scriptName :: String                      -- ^ The initial portion o....
  ,  pathInfo :: String                        -- ^ The remainder of the ....
  ,  queryString :: String                     -- ^ The portion of the re....
  ,  serverName :: String                      -- ^ When combined with SC....
  ,  serverPort :: Int                         -- ^ preference to SERVER_....
  ,  http    :: [(String, String)]              -- ^ All http header varia....
  ,  hackVersion :: [Int]                      -- ^ The Array [0,1], repr....
  ,  hackUrlScheme :: Hack_UrlScheme          -- ^ HTTP or HTTPS, depend....
  ,  hackInput :: B.ByteString              -- ^ body of the request
  ,  hackErrors :: HackErrors                  -- ^ error stream
  ,  hackHeaders    :: [(String, String)]      -- ^ custom headers, inten....
  }
  deriving (Show) -- careful with showing this, it now causes an infinite
                  -- loop with certain handlers due to the use of a
                  -- lazy bytestring

Response defined by

data Response = Response
  {  status :: Int                              -- ^ must be greater than ....
  ,  headers :: [(String, String)]              -- ^ The header must not c....
  ,  body :: B.ByteString                       -- ^ body of the response
  }
  deriving (Show)

Let's dive in some more

Let's take for example the first line of code in our example:

name <- ask ^ params ^ lookup "name" ^ fromMaybe "nobody"

What happens here:

Templating using Network.Loly.Template

Uses StateMonads update function to update Response setting content-type and body.

html :: String -> AppUnit
html x = do
  update - set_content_type _TextHtml
  update - set_body (x.fromString)
  render_layout

Hacks middleware on Loli level

Network.Loli.Engine

add_middleware :: Middleware -> Loli -> Loli
add_middleware x s = 
  let xs = s.middlewares in s {middlewares = xs.insert_last x}

And ofcourse defined in Network.Loli.DSL on unit level.

middleware :: Middleware -> Unit
middleware = add_middleware > update

Loli Engine

Contains code

loli :: Unit -> Application
loli unit = run unit not_found_app
  where
    not_found_app = not_found dummy_app
    run_route x = (x.router) loli_captures run_app (x.route_path)

    run :: Unit -> Middleware
    run unit' = 
      let loli_state    = execState unit' def
          route_configs = loli_state.routes
          route         = route_configs.map run_route .use
          mime_filter   = user_mime (loli_state.mimes)
          stack         = loli_state.middlewares.use
          pre           = pre_installed_middlewares.use
      in
      use [pre, mime_filter, stack, route]

Where use is defined as:

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

essentially right to left composition of all middlewares, thus wrapping them in one another:

Routing

data RouteConfig = RouteConfig
  {
    route_path :: RoutePath
  , router     :: Router
  }

data Loli = Loli
  {
    current_router  :: Router
  , routes          :: [RouteConfig]
  , middlewares     :: [Middleware]
  , mimes           :: Assoc
  }

  instance Default Loli where
    def = Loli loli_router def [dummy_middleware] def

Zipping up ..

This is just a quick glance at how Hack and Loli where implemented. Shedding some light on the structure of this approach to web apps inside haskell.


Fork me on GitHub