hyena + happstack-state
The good news is, there is nothing to stop you from using happstack with hyena today. The code in this section works using unmodified versions happstack 0.1 and hyena.
The trade-off is that you will not have access to most of the
features provided by happstack-server, such as the dir, path,
method, fileServe, etc
.
In a later section we will show that this functionality can be rebuilt on top of hyena.
This tutorial assumes your are a little bit familiar with happstack-state already and are interested in trying out hyena. In the first part I provide a very simple hyena+happstack-state application. This is a useful starting point for your own application.
In the second part, I will go more in-depth into hyena and Enumerators
.
Anyway, on to the code. We are going to implement a simple hit counter application. First we just enable a bunch of language extensions that happstack-state requires, and import a bunch of modules.
> {-# LANGUAGE GeneralizedNewtypeDeriving, ImpredicativeTypes, TemplateHaskell, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses, UndecidableInstances, DeriveDataTypeable, TypeFamilies, RankNTypes, TypeSynonymInstances #-} > module Main where
> import Control.Concurrent (forkIO) > import Control.Monad.State (MonadState(get,put)) > import qualified Data.ByteString as S > import qualified Data.ByteString.Char8 as C (pack, unpack) > import Happstack.Data (Default(defaultValue),deriveAll) > import Happstack.State (Component(..),Proxy(..), Version(..),End, createCheckpoint, deriveSerialize, mkMethods, shutdownSystem, startSystemState, update, waitForTermination) > import Happstack.Server.Cron (cron) > import Hyena.Server (serve) > import Network.Wai (Application, Enumerator) > > -- * State
Next we implement a happstack-state component which stores the number of requests we have received. This code is in no way hyena specific.
First we declare a simple type for counting requests.
> > $(deriveAll [''Read, ''Show, ''Eq ,''Ord, ''Default, ''Num, ''Enum] > [d| > newtype Hits = Hits Integer > |])
Next we create Serialize
and Version
instances so that we can use the Hits
type with
happstack-state.
> $(deriveSerialize ''Hits) > instance Version Hits
Now we create a Component
for the Hits
type.
> instance Component Hits where > type Dependencies Hits = End > initialValue = defaultValue
Then we create a simple function which increments the number of hits, and returns to use the current (updated) count.
> inc :: (MonadState Hits m) => m Hits > inc = > do hits <- get > let hits' = succ hits > put hits' > return hits'
And, then we turn the function into a method that can be used with
update
.
> $(mkMethods ''Hits ['inc])
> -- * main
Next we move onto the main function. This main function is almost
exactly what we would have for a happstack-server based
program, except the traditional simpleHTTP conf impl
is
replaced with the hyena equivalent server
hitApplication
.
> main :: IO () > main = > do ctl <- startSystemState (Proxy :: Proxy Hits) > forkIO $ cron (60*60*24) (createCheckpoint ctl) > forkIO $ serve hitApplication > putStrLn "running..." > waitForTermination > createCheckpoint ctl > shutdownSystem ctl
An Application
is a 4-tuple which consists of an HTTP
return code (200, 404, etc), a string associated with that return
code (OK, Not Found, etc), a list of HTTP headers, and an enumerator
which generates the body of the HTTP response.
> hitApplication :: Application > hitApplication environ = do > return (200, C.pack "OK", [textPlain, closeC], showHits)
There are two important headers set for the hit application. The
first is simply the Content-type: text/plain
header.
> textPlain :: (S.ByteString, S.ByteString) > textPlain = (C.pack "Content-type", C.pack "text/plain")
The second header is Connection: close
. This tells
hyena that it should close the connection after the enumerator has
finished outputting the body. This is required because HTTP 1.1
specifies that all HTTP connections are 'keep-alive' by default.
> closeC :: (S.ByteString, S.ByteString) > closeC = (C.pack "Connection", C.pack "close")
There are three ways that an HTTP connection can be closed:
Content-length
header and
the client closes the connection after downloading the specified
number of bytes.Connection: close
header
in the Response and then closes the connection after it sends
the body.Connection: close
header in
the Request. The server notes this and closes the connection after
sending the body.All three of these methods work in hyena. If none of the above conditions are meet, then hyena assumes that you don't want the connection closed.
Finally we have our Enumerator
which generates the
HTTP response body:
> showHits :: Enumerator > showHits = > let yieldHits f z = do > hits <- update Inc > z' <- f z (C.pack $ "hello, you are visitor number: " ++ show hits ++ "\n") > case z' of > (Left z'') -> return z'' > (Right z'') -> return z'' > in > yieldHits
This Enumerator
is very boring. It outputs one line
of text, and then it is done. It is not a particular instructive
example of an Enumerator
, so rather than trying to
understand it now, I recommend moving on to the next section where we
will examine Enumerators
using more instructive examples.