{-# OPTIONS_GHC -F -pgmFtrhsx #-} import Happstack.Server import HSP import Happstack.Server.HSP.HTML import Data.Monoid {- We define a very simple data type here to use as our instance for FromData -} data Foo = Foo {bar :: Int, baz :: Int} deriving Show {- Defining an instance of FromData is fundamentally simple. Primarily, you should use the helper function look to grab the string associated with the named parameter you provide. From there, we use read to parse the string into an int and return the final Foo. This isn't the safest construction, because the read could fail, but you can easily provide yourself with more safety by using the MonadPlus instance of RqData and just calling mzero when an error occurs.-} instance FromData Foo where fromData = do x <- read `fmap` look "bar" y <- read `fmap` look "baz" return $ Foo x y main :: IO () main = simpleHTTP nullConf{port=8080} $ (dir "getHandler" handler) `mappend` (dir "postHandler" handler) `mappend` home {- Please note that we actually use the same handler for both GET & POST requests. This is an advantage of using FromData. -} handler :: ServerPartT IO Response handler = do mfoo <- getData case mfoo of Nothing -> webHSP $ didn'twork Just foo -> webHSP $ displayFoo foo displayFoo :: Foo -> HSP XML displayFoo f = This is a Foo

Here, look at a Foo: <%show f%>

home

didn'twork = Something is wrong!

Something has gone horribly wrong go home

home :: ServerPartT IO Response home = webHSP $ Get and Post examples