[Haskell-cafe] happs tutorial

Anatoly Yakovenko aeyakovenko at gmail.com
Sat Jun 2 21:37:32 EDT 2007


can someone help me get the first part of the tutorial working with happs 0.8.8

http://happs.org/HAppS/doc/tutorial.html

this part at least :

module Main where

import HAppS
import Control.Monad.State

data MyState = MyState String deriving (Read, Show)

instance StartState MyState where
        startStateM = return $ MyState "Hello World!"
instance Serialize MyState where
        typeString _ = "MyState"
        encodeStringM = defaultEncodeStringM
        decodeStringM = defaultDecodeStringM

app :: Method -> Host -> [String] -> Ev MyState Request Result
app _ _ _ = do
        MyState message <- get
        sresult 200 message

main = stdMain $ simpleHTTP "" [] app :*: End

I am having a hard time getting everything to compile.  Also, why is

> :t HAppS.simpleHTTP
HAppS.simpleHTTP :: forall st.
[ServerPart (Ev st Request) Request IO Result]
-> Conf
-> Handler st

but the type in this
http://happs.org/auto/apidoc/HAppS-Protocols-SimpleHTTP.html#v%3AsimpleFileServe
docs is
simpleHTTP :: XSLPath -> [(String, String)] -> (Method -> Host ->
[String] -> Ev st Request Result) -> Conf -> Handler st


More information about the Haskell-Cafe mailing list