pieter:
Hello,
I'm trying to write a simple module for the haskell web server (hws-
cgi).
And I would like to write a simple module that maintains some kind of
state for a session.
But I'm I write I cannot do this in pure Haskell ? Without adopting
the sources of the Haskell web server ?
I'll examplify to make it more concrete :
The requestHandler function a module has to implement has this
signature.
requestHandler :: ServerState -> ServerRequest -> IO (Maybe Response)
Let 's assume I have this implementation
requestHandler st _ = return $ Just $ mkRequest
where mkRequest =
okResponse (serverConfig st) mkBody hs True
mkBody = HereItIs " This is a test"
hs = mkHeaders [contentTypeHeader "text/html"]
And I would like the response to include, for example, a number
indicating the number of calls that has been handled by the module.
I would concider using an Mvar but I can't "remember" the mvar
between requests.
Am I right to assume that the interface of the requestHandler method
has to be adapted ? Or that serverstate has to be adopted so that it
can act as a datastore ?
I don't think so.
You could, for example store the count on disk, and read it back in. Or
you could simulate a disk store by using a mutable variable, hidden in
your module:
module M (requestHandler) where
import Control.Concurrent.MVar
import System.IO.Unsafe
--
-- A threadsafe mutable variable, internal to this module. Rather
-- than use, say, a disk file as storage, we can keep the count here.
--
countRef :: MVar Int
countRef = unsafePerformIO $ newMVar 0
{-# NOINLINE countRef #-}
------------------------------------------------------------------------
-- And a quick example:
type Response = Int
requestHandler :: IO (Maybe Response)
requestHandler = do
n <- modifyMVar countRef $ \c -> return (c+1, c)
print $ "received " ++ show n ++ " requests."
return $ case n of
0 -> Nothing
_ -> Just n
*Main> requestHandler
"received 0 requests."
Nothing
*Main> requestHandler
"received 1 requests."
Just 1
*Main> requestHandler
"received 2 requests."
Just 2
*Main> requestHandler
"received 3 requests."
Just 3
This seems simpler than writing the count to disk. And as long as you
stay in IO, perfectly safe.
In the longer term, you might want to look at state-parameterised
plugins for the HWS. We do this in lambdabot, associating a private
state type with each plugin, which is managed by the main server. The
plugins can then get or set internal state, without resorting to local
mutable variables.
-- Don