happstack-server-0.4.1: Web related tools and services.Source codeContentsIndex
Happstack.Server.SimpleHTTP
Portabilityrequires mtl
Stabilityprovisional
Maintainerlemmih@vo.com
Contents
SimpleHTTP
ServerPartT
WebT
Type Classes
Manipulating requests
Manipulating responses
guards and building blocks
proxying
unknown
Parsing input and cookies
XSLT
Error Handlng
Output Validation
Description

SimpleHTTP provides a back-end independent API for handling HTTP requests.

By default, the built-in HTTP server will be used. However, other back-ends like CGI/FastCGI can used if so desired.

So the general nature of simpleHTTP is no different than what you'd expect from a web application container. First you figure out which function is going to process your request, process the request to generate a response, then return that response to the client. The web application container is started with simpleHTTP, which takes a configuration and a response-building structure (ServerPartT which I'll return too in a moment), and picks the first handler that is willing to accept the request, passes the request into the handler. A simple hello world style HAppS simpleHTTP server looks like:

   main = simpleHTTP nullConf $ return "Hello World!"

simpleHTTP nullConf creates a HTTP server on port 8000. return "Hello World!" creates a serverPartT that just returns that text.

ServerPartT is the basic response builder. As you might expect, it's a container for a function that takes a Request and converts it a response suitable for sending back to the server. Most of the time though you don't even need to worry about that as ServerPartT hides almost all the machinery for building your response by exposing a few type classes.

ServerPartT is a pretty rich monad. You can interact with your request, your response, do IO, etc. Here is a do block that validates basic authentication It takes a realm name as a string, a Map of username to password and a server part to run if authentication fails.

basicAuth' acts like a guard, and only produces a response when authentication fails. So put it before any ServerPartT you want to demand authentication for in any collection of ServerPartTs.


main = simpleHTTP nullConf $ myAuth, return "Hello World!"
     where
         myAuth = basicAuth' "Test"
             (M.fromList [("hello", "world")]) (return "Login Failed")

basicAuth' realmName authMap unauthorizedPart =
    do
        let validLogin name pass = M.lookup name authMap == Just pass
        let parseHeader = break (':'==) . Base64.decode . B.unpack . B.drop 6
        authHeader <- getHeaderM "authorization"
        case authHeader of
            Nothing -> err
            Just x  -> case parseHeader x of
                (name, ':':pass) | validLogin name pass -> mzero
                                   | otherwise -> err
                _                                       -> err
    where
        err = do
            unauthorized ()
            setHeaderM headerName headerValue
            unauthorizedPart
        headerValue = "Basic realm=\"" ++ realmName ++ "\""
        headerName  = "WWW-Authenticate"

Here is another example that uses liftIO to embed IO in a request process

   main = simpleHTTP nullConf $ myPart
   myPart = do
     line <- liftIO $ do -- IO
         putStr "return? "
         getLine
     when (take 2 line /= "ok") $ (notfound () >> return "refused")
     return "Hello World!"

This example will ask in the console "return? " if you type "ok" it will show "Hello World!" and if you type anything else it will return a 404.

Synopsis
module Happstack.Server.HTTP.Types
module Happstack.Server.Cookie
simpleHTTP :: ToMessage a => Conf -> ServerPartT IO a -> IO ()
simpleHTTP' :: (ToMessage b, Monad m, Functor m) => (UnWebT m a -> UnWebT IO b) -> Conf -> ServerPartT m a -> IO ()
simpleHTTP'' :: (ToMessage b, Monad m, Functor m) => ServerPartT m b -> Request -> m Response
simpleHTTPWithSocket :: ToMessage a => Socket -> Conf -> ServerPartT IO a -> IO ()
simpleHTTPWithSocket' :: (ToMessage b, Monad m, Functor m) => (UnWebT m a -> UnWebT IO b) -> Socket -> Conf -> ServerPartT m a -> IO ()
bindPort :: Conf -> IO Socket
parseConfig :: [String] -> Either [String] Conf
newtype ServerPartT m a = ServerPartT {
unServerPartT :: ReaderT Request (WebT m) a
}
type ServerPart a = ServerPartT IO a
runServerPartT :: ServerPartT m a -> Request -> WebT m a
mapServerPartT :: (UnWebT m a -> UnWebT n b) -> ServerPartT m a -> ServerPartT n b
mapServerPartT' :: (Request -> UnWebT m a -> UnWebT n b) -> ServerPartT m a -> ServerPartT n b
withRequest :: (Request -> WebT m a) -> ServerPartT m a
anyRequest :: Monad m => WebT m a -> ServerPartT m a
newtype WebT m a = WebT {
unWebT :: ErrorT Response (FilterT Response (MaybeT m)) a
}
type UnWebT m a = m (Maybe (Either Response a, FilterFun Response))
type FilterFun a = SetAppend (Dual (Endo a))
type Web a = WebT IO a
mkWebT :: UnWebT m a -> WebT m a
ununWebT :: WebT m a -> UnWebT m a
runWebT :: forall m b. (Functor m, ToMessage b) => WebT m b -> m (Maybe Response)
mapWebT :: (UnWebT m a -> UnWebT n b) -> WebT m a -> WebT n b
class FromReqURI a where
fromReqURI :: String -> Maybe a
class ToMessage a where
toContentType :: a -> ByteString
toMessage :: a -> ByteString
toResponse :: a -> Response
class FromData a where
fromData :: RqData a
class Monad m => ServerMonad m where
askRq :: m Request
localRq :: (Request -> Request) -> m a -> m a
type RqData a = ReaderT ([(String, Input)], [(String, Cookie)]) Maybe a
noHandle :: MonadPlus m => m a
getHeaderM :: ServerMonad m => String -> m (Maybe ByteString)
escape :: (WebMonad a m, FilterMonad a m) => m a -> m b
escape' :: (WebMonad a m, FilterMonad a m) => a -> m b
multi :: Monad m => [ServerPartT m a] -> ServerPartT m a
class Monad m => FilterMonad a m | m -> a where
setFilter :: (a -> a) -> m ()
composeFilter :: (a -> a) -> m ()
getFilter :: m b -> m (b, a -> a)
ignoreFilters :: FilterMonad a m => m ()
data SetAppend a
= Set a
| Append a
newtype FilterT a m b = FilterT {
unFilterT :: WriterT (FilterFun a) m b
}
class Monad m => WebMonad a m | m -> a where
finishWith :: a -> m b
ok :: FilterMonad Response m => a -> m a
modifyResponse :: FilterMonad a m => (a -> a) -> m ()
setResponseCode :: FilterMonad Response m => Int -> m ()
badGateway :: FilterMonad Response m => a -> m a
internalServerError :: FilterMonad Response m => a -> m a
badRequest :: FilterMonad Response m => a -> m a
unauthorized :: FilterMonad Response m => a -> m a
forbidden :: FilterMonad Response m => a -> m a
notFound :: FilterMonad Response m => a -> m a
seeOther :: (FilterMonad Response m, ToSURI uri) => uri -> res -> m res
found :: (FilterMonad Response m, ToSURI uri) => uri -> res -> m res
movedPermanently :: (FilterMonad Response m, ToSURI a) => a -> res -> m res
tempRedirect :: (FilterMonad Response m, ToSURI a) => a -> res -> m res
addCookie :: FilterMonad Response m => Seconds -> Cookie -> m ()
addCookies :: FilterMonad Response m => [(Seconds, Cookie)] -> m ()
addHeaderM :: FilterMonad Response m => String -> String -> m ()
setHeaderM :: FilterMonad Response m => String -> String -> m ()
ifModifiedSince :: CalendarTime -> Request -> Response -> Response
guardRq :: (ServerMonad m, MonadPlus m) => (Request -> Bool) -> m ()
dir :: (ServerMonad m, MonadPlus m) => String -> m a -> m a
host :: (ServerMonad m, MonadPlus m) => String -> m a -> m a
withHost :: (ServerMonad m, MonadPlus m) => (String -> m a) -> m a
method :: (MatchMethod method, Monad m) => method -> WebT m a -> ServerPartT m a
methodSP :: (ServerMonad m, MonadPlus m, MatchMethod method) => method -> m b -> m b
methodM :: (ServerMonad m, MonadPlus m, MatchMethod method) => method -> m ()
methodOnly :: (ServerMonad m, MonadPlus m, MatchMethod method) => method -> m ()
nullDir :: (ServerMonad m, MonadPlus m) => m ()
path :: (FromReqURI a, MonadPlus m, ServerMonad m) => (a -> m b) -> m b
anyPath :: (ServerMonad m, MonadPlus m) => m r -> m r
anyPath' :: (ServerMonad m, MonadPlus m) => m r -> m r
trailingSlash :: (ServerMonad m, MonadPlus m) => m ()
withData :: (FromData a, MonadPlus m, ServerMonad m) => (a -> m r) -> m r
withDataFn :: (MonadPlus m, ServerMonad m) => RqData a -> (a -> m r) -> m r
getDataFn :: ServerMonad m => RqData a -> m (Maybe a)
getData :: (ServerMonad m, FromData a) => m (Maybe a)
require :: (MonadIO m, MonadPlus m) => IO (Maybe a) -> (a -> m r) -> m r
requireM :: (MonadTrans t, Monad m, MonadPlus (t m)) => m (Maybe a) -> (a -> t m r) -> t m r
basicAuth :: (WebMonad Response m, ServerMonad m, FilterMonad Response m, MonadPlus m) => String -> Map String String -> m a -> m a
uriRest :: ServerMonad m => (String -> m a) -> m a
flatten :: (ToMessage a, Functor f) => f a -> f Response
localContext :: Monad m => (WebT m a -> WebT m' a) -> ServerPartT m a -> ServerPartT m' a
proxyServe :: (MonadIO m, WebMonad Response m, ServerMonad m, MonadPlus m, FilterMonad Response m) => [String] -> m Response
rproxyServe :: MonadIO m => String -> [(String, String)] -> ServerPartT m Response
debugFilter :: (MonadIO m, Show a) => ServerPartT m a -> ServerPartT m a
applyRequest :: (ToMessage a, Monad m, Functor m) => ServerPartT m a -> Request -> Either (m Response) b
lookInput :: String -> RqData Input
lookBS :: String -> RqData ByteString
look :: String -> RqData String
lookCookie :: String -> RqData Cookie
lookCookieValue :: String -> RqData String
readCookieValue :: Read a => String -> RqData a
lookRead :: Read a => String -> RqData a
lookPairs :: RqData [(String, String)]
xslt :: (MonadIO m, MonadPlus m, ToMessage r) => XSLTCmd -> XSLPath -> m r -> m Response
doXslt :: MonadIO m => XSLTCmd -> XSLPath -> Response -> m Response
errorHandlerSP :: (Monad m, Error e) => (Request -> e -> WebT m a) -> ServerPartT (ErrorT e m) a -> ServerPartT m a
simpleErrorHandler :: Monad m => String -> ServerPartT m Response
spUnwrapErrorT :: Monad m => (e -> ServerPartT m a) -> Request -> UnWebT (ErrorT e m) a -> UnWebT m a
setValidator :: (Response -> IO Response) -> Response -> Response
setValidatorSP :: (Monad m, ToMessage r) => (Response -> IO Response) -> m r -> m Response
validateConf :: Conf
runValidator :: (Response -> IO Response) -> Response -> IO Response
wdgHTMLValidator :: (MonadIO m, ToMessage r) => r -> m Response
noopValidator :: Response -> IO Response
lazyProcValidator :: FilePath -> [String] -> Maybe FilePath -> Maybe [(String, String)] -> (Maybe ByteString -> Bool) -> Response -> IO Response
Documentation
module Happstack.Server.HTTP.Types
module Happstack.Server.Cookie
SimpleHTTP
simpleHTTP :: ToMessage a => Conf -> ServerPartT IO a -> IO ()Source
Use the built-in web-server to serve requests according to a ServerPartT. Use msum to pick the first handler from a list of handlers that doesn't call noHandle.
simpleHTTP' :: (ToMessage b, Monad m, Functor m) => (UnWebT m a -> UnWebT IO b) -> Conf -> ServerPartT m a -> IO ()Source
a combination of simpleHTTP'' and mapServerPartT. See mapServerPartT for a discussion of the first argument of this function.
simpleHTTP'' :: (ToMessage b, Monad m, Functor m) => ServerPartT m b -> Request -> m ResponseSource
Generate a result from a ServerPart and a Request. This is mainly used by CGI (and fast-cgi) wrappers.
simpleHTTPWithSocket :: ToMessage a => Socket -> Conf -> ServerPartT IO a -> IO ()Source

Run simpleHTTP with a previously bound socket. Useful if you want to run happstack as user on port 80. Use something like this:

 import System.Posix.User (setUserID, UserEntry(..), getUserEntryForName)

 main = do
     let conf = nullConf { port = 80 }
     socket <- bindPort conf
     -- do other stuff as root here
     getUserEntryForName "www" >>= setUserID . userID
     -- finally start handling incoming requests
     tid <- forkIO $ socketSimpleHTTP socket conf impl

Note: It's important to use the same conf (or at least the same port) for bindPort and simpleHTTPWithSocket.

simpleHTTPWithSocket' :: (ToMessage b, Monad m, Functor m) => (UnWebT m a -> UnWebT IO b) -> Socket -> Conf -> ServerPartT m a -> IO ()Source
simpleHTTP' with a socket
bindPort :: Conf -> IO SocketSource
Bind port and return the socket for simpleHTTPWithSocket
parseConfig :: [String] -> Either [String] ConfSource
parseConfig tries to parse your command line options into a Conf.
ServerPartT
newtype ServerPartT m a Source
ServerPartT is a container for processing requests and returning results
Constructors
ServerPartT
unServerPartT :: ReaderT Request (WebT m) a
show/hide Instances
type ServerPart a = ServerPartT IO aSource
An alias for using ServerPartT when using the IO
runServerPartT :: ServerPartT m a -> Request -> WebT m aSource
particularly useful when combined with runWebT to produce a m (Maybe Response) from a request.
mapServerPartT :: (UnWebT m a -> UnWebT n b) -> ServerPartT m a -> ServerPartT n bSource

Used to manipulate the containing monad. Very useful when embedding a monad into a ServerPartT, since simpleHTTP requires a ServerPartT IO a. Refer to WebT for an explanation of the structure of the monad.

Here is an example. Suppose you want to embed an ErrorT into your ServerPartT to enable throwError and catchError in your Monad.

   type MyServerPartT e m a = ServerPartT (ErrorT e m) a

Now suppose you want to pass MyServerPartT into a function that demands a ServerPartT IO a (e.g. simpleHTTP). You can provide the function:

   unpackErrorT:: (Monad m, Show e) => UnWebT (ErrorT e m) a -> UnWebT m a
   unpackErrorT handler et = do
      eitherV <- runErrorT et
      case eitherV of
          Left err -> return $ Just (Left Catastrophic failure  ++ show e, Set $ Endo r -> r{rsCode = 500})
          Right x -> return x

With unpackErrorT you can now call simpleHTTP. Just wrap your ServerPartT list.

   simpleHTTP nullConf $ mapServerPartT unpackErrorT (myPart `catchError` myHandler)

Or alternatively:

   simpleHTTP' unpackErrorT nullConf (myPart `catchError` myHandler)

Also see spUnwrapErrorT for a more sophisticated version of this function

mapServerPartT' :: (Request -> UnWebT m a -> UnWebT n b) -> ServerPartT m a -> ServerPartT n bSource
A varient of mapServerPartT where the first argument, also takes a request. useful if you want to runServerPartT on a different ServerPartT inside your monad (see spUnwrapErrorT)
withRequest :: (Request -> WebT m a) -> ServerPartT m aSource
anyRequest :: Monad m => WebT m a -> ServerPartT m aSource
a constructor for a ServerPartT when you don't care about the request
WebT
newtype WebT m a Source
The basic response building object.
Constructors
WebT
unWebT :: ErrorT Response (FilterT Response (MaybeT m)) a
show/hide Instances
type UnWebT m a = m (Maybe (Either Response a, FilterFun Response))Source

It is worth discussing the unpacked structure of WebT a bit as it's exposed in mapServerPartT and mapWebT.

A fully unpacked WebT has a structure that looks like:

    ununWebT $ WebT m a :: m (Maybe (Either Response a, FilterFun Response))

So, ignoring m, as it is just the containing Monad, the outermost layer is a Maybe. This is Nothing if mzero was called or Just (Either Response a, SetAppend (Endo Response)) if mzero wasn't called. Inside the Maybe, there is a pair. The second element of the pair is our filter function FilterFun Response. FilterFun Response is a type alias for SetAppend (Dual (Endo Response)). This is just a wrapper for a Response->Response function with a particular Monoid behavior. The value

      Append (Dual (Endo f))

Causes f to be composed with the previous filter.

      Set (Dual (Endo f))

Causes f to not be composed with the previous filter.

Finally, the first element of the pair is either Left Response or Right a.

Another way of looking at all these pieces is from the behaviors they control. The Maybe controls the mzero behavior. Set (Endo f) comes from the setFilter behavior. Likewise, Append (Endo f) is from composeFilter. Left Response is what you get when you call finishWith and Right a is the normal exit.

An example case statement looks like: ex1 webt = do val <- ununWebT webt case val of Nothing -> Nothing -- this is the interior value when mzero was used Just (Left r, f) -> Just (Left r, f) -- r is the value that was passed into finishWith -- f is our filter function Just (Right a, f) -> Just (Right a, f) -- a is our normal monadic value -- f is still our filter function

type FilterFun a = SetAppend (Dual (Endo a))Source
FilterFun is a lot more fun to type than SetAppend (Dual (Endo a))
type Web a = WebT IO aSource
An alias for WebT when using IO
mkWebT :: UnWebT m a -> WebT m aSource
for wrapping a WebT back up. mkWebT . ununWebT = id
ununWebT :: WebT m a -> UnWebT m aSource
for when you really need to unpack a WebT entirely (and not just unwrap the first layer with unWebT)
runWebT :: forall m b. (Functor m, ToMessage b) => WebT m b -> m (Maybe Response)Source
takes your WebT, if it is mempty it returns Nothing else it converts the value to a Response and applies your filter to it.
mapWebT :: (UnWebT m a -> UnWebT n b) -> WebT m a -> WebT n bSource
see mapServerPartT for a discussion of this function
Type Classes
class FromReqURI a whereSource

This class is used by path to parse a path component into a value. At present, the instances for number types (Int, Float, etc) just call readM. The instance for String however, just passes the path component straight through. This is so that you can read a path component which looks like this as a String:

/somestring/

instead of requiring the path component to look like:

/somestring/

Methods
fromReqURI :: String -> Maybe aSource
show/hide Instances
class ToMessage a whereSource

Minimal definition: toMessage

Used to convert arbitrary types into an HTTP response. You need to implement this if you want to pass ServerPartT m containing your type into simpleHTTP

Methods
toContentType :: a -> ByteStringSource
toMessage :: a -> ByteStringSource
toResponse :: a -> ResponseSource
show/hide Instances
Manipulating requests
class FromData a whereSource
Useful for withData and getData' implement this on your preferred type to use those functions
Methods
fromData :: RqData aSource
show/hide Instances
(Eq a, Show a, Xml a, Data a) => FromData a
FromData a => FromData (Maybe a)
(FromData a, FromData b) => FromData (a, b)
(FromData a, FromData b, FromData c) => FromData (a, b, c)
(FromData a, FromData b, FromData c, FromData d) => FromData (a, b, c, d)
class Monad m => ServerMonad m whereSource
yes, this is exactly like ReaderT with new names. Why you ask? Because ServerT can lift up a ReaderT. If you did that, it would shadow ServerT's behavior as a ReaderT, thus meaning if you lifted the ReaderT you could no longer modify the Request. This way you can add a ReaderT to your monad stack without any trouble.
Methods
askRq :: m RequestSource
localRq :: (Request -> Request) -> m a -> m aSource
show/hide Instances
type RqData a = ReaderT ([(String, Input)], [(String, Cookie)]) Maybe aSource
noHandle :: MonadPlus m => m aSource
deprecated. use mzero
getHeaderM :: ServerMonad m => String -> m (Maybe ByteString)Source
Get a header out of the request
escape :: (WebMonad a m, FilterMonad a m) => m a -> m bSource
Used to ignore all your filters and immediately end the computation. A combination of ignoreFilters and finishWith
escape' :: (WebMonad a m, FilterMonad a m) => a -> m bSource
An alternate form of escape that can be easily used within a do block.
multi :: Monad m => [ServerPartT m a] -> ServerPartT m aSource
deprecated. Just use msum
Manipulating responses
class Monad m => FilterMonad a m | m -> a whereSource
A set of functions for manipulating filters. A ServerPartT implements FilterMonad Response so these methods are the fundamental ways of manipulating the response object, especially before you've converted your monadic value to a Response
Methods
setFilter :: (a -> a) -> m ()Source

Ignores all previous alterations to your filter

As an example:

   do
     composeFilter f
     setFilter g
     return "Hello World"

setFilter g will cause the first composeFilter to be ignored.

composeFilter :: (a -> a) -> m ()Source
composes your filter function with the existing filter function.
getFilter :: m b -> m (b, a -> a)Source
retrives the filter from the environment
show/hide Instances
ignoreFilters :: FilterMonad a m => m ()Source
An alias for setFilter id It resets all your filters
data SetAppend a Source

A monoid operation container. If a is a monoid, then SetAppend is a monoid with the following behaviors:

   Set    x mappend Append y = Set    (x mappend y)
   Append x mappend Append y = Append (x mappend y)
   _       mappend Set y    = Set y

A simple way of sumerizing this is, if the right side is Append, then the right is appended to the left. If the right side is Set, then the left side is ignored.

Constructors
Set a
Append a
show/hide Instances
newtype FilterT a m b Source
Constructors
FilterT
unFilterT :: WriterT (FilterFun a) m b
show/hide Instances
class Monad m => WebMonad a m | m -> a whereSource
Methods
finishWith :: a -> m bSource

A control structure It ends the computation and returns the Response you passed into it immediately. This provides an alternate escape route. In particular it has a monadic value of any type. And unless you call setFilter id first your response filters will be applied normally.

Extremely useful when you're deep inside a monad and decide that you want to return a completely different content type, since it doesn't force you to convert all your return types to Response early just to accomodate this.

show/hide Instances
ok :: FilterMonad Response m => a -> m aSource
Respond with 200 OK.
modifyResponse :: FilterMonad a m => (a -> a) -> m ()Source
deprecated. Same as composeFilter
setResponseCode :: FilterMonad Response m => Int -> m ()Source
sets the return code in your response
badGateway :: FilterMonad Response m => a -> m aSource
Responds with 502 Bad Gateway
internalServerError :: FilterMonad Response m => a -> m aSource
Respond with 500 Interal Server Error
badRequest :: FilterMonad Response m => a -> m aSource
Respond with 400 Bad Request.
unauthorized :: FilterMonad Response m => a -> m aSource
Respond with 401 Unauthorized.
forbidden :: FilterMonad Response m => a -> m aSource
Respond with 403 Forbidden.
notFound :: FilterMonad Response m => a -> m aSource
Respond with 404 Not Found.
seeOther :: (FilterMonad Response m, ToSURI uri) => uri -> res -> m resSource
Respond with 303 See Other.
found :: (FilterMonad Response m, ToSURI uri) => uri -> res -> m resSource
Respond with 302 Found.
movedPermanently :: (FilterMonad Response m, ToSURI a) => a -> res -> m resSource
Respond with 301 Moved Permanently.
tempRedirect :: (FilterMonad Response m, ToSURI a) => a -> res -> m resSource
Respond with 307 Temporary Redirect.
addCookie :: FilterMonad Response m => Seconds -> Cookie -> m ()Source
adds the cookie with a timeout to the response
addCookies :: FilterMonad Response m => [(Seconds, Cookie)] -> m ()Source
adds the list of cookie timeout pairs to the response
addHeaderM :: FilterMonad Response m => String -> String -> m ()Source
adds headers into the response. This method does not overwrite any existing header of the same name, hence the name addHeaderM. If you want to replace a header use setHeaderM.
setHeaderM :: FilterMonad Response m => String -> String -> m ()Source
sets a header into the response. This will replace an existing header of the same name. Use addHeaderM, if you want to add more than one header of the same name.
ifModifiedSinceSource
:: CalendarTimemod-time for the Response (MUST NOT be later than server's time of message origination)
-> Requestincoming request (used to check for if-modified-since)
-> ResponseResponse to send if there are modifications
-> Response
honor if-modified-since header in Request If the Request includes the if-modified-since header and the Response has not been modified, then return 304 (Not Modified), otherwise return the Response.
guards and building blocks
guardRq :: (ServerMonad m, MonadPlus m) => (Request -> Bool) -> m ()Source
guard using an arbitrary function on the request
dir :: (ServerMonad m, MonadPlus m) => String -> m a -> m aSource
Pop a path element and run the ServerPartT if it matches the given string.
host :: (ServerMonad m, MonadPlus m) => String -> m a -> m aSource
Guard against the host
withHost :: (ServerMonad m, MonadPlus m) => (String -> m a) -> m aSource
Lookup the host header and pass it to the handler
method :: (MatchMethod method, Monad m) => method -> WebT m a -> ServerPartT m aSource
Guard against the method. Note, this function also guards against any remaining path segments. This function id deprecated. You can probably just use methodSP (or methodM) now.
methodSP :: (ServerMonad m, MonadPlus m, MatchMethod method) => method -> m b -> m bSource
Guard against the method. Note, this function also guards against any remaining path segments.
methodM :: (ServerMonad m, MonadPlus m, MatchMethod method) => method -> m ()Source
Guard against the method. This function also guards against any remaining path segments. See methodOnly for the version that guards only by method
methodOnly :: (ServerMonad m, MonadPlus m, MatchMethod method) => method -> m ()Source
guard against the method only. (as opposed to methodM)
nullDir :: (ServerMonad m, MonadPlus m) => m ()Source
Guard against non-empty remaining path segments
path :: (FromReqURI a, MonadPlus m, ServerMonad m) => (a -> m b) -> m bSource
Pop a path element and parse it using the fromReqURI in the FromReqURI class.
anyPath :: (ServerMonad m, MonadPlus m) => m r -> m rSource

pops any path element and ignores when chosing a ServerPartT to handle the

request.

anyPath' :: (ServerMonad m, MonadPlus m) => m r -> m rSource
Deprecated. Use anyPath.
trailingSlash :: (ServerMonad m, MonadPlus m) => m ()Source
guard which checks that the Request URI ends in \/. Useful for distinguishing between foo and foo/
withData :: (FromData a, MonadPlus m, ServerMonad m) => (a -> m r) -> m rSource
Retrieve data from the input query or the cookies.
withDataFn :: (MonadPlus m, ServerMonad m) => RqData a -> (a -> m r) -> m rSource
withDataFn is like with data, but you pass in a RqData monad for reading.
getDataFn :: ServerMonad m => RqData a -> m (Maybe a)Source

used to read parse your request with a RqData (a ReaderT, basically) For example here is a simple GET or POST variable based authentication guard. It handles the request with errorHandler if authentication fails.

   myRqData = do
      username <- lookInput "username"
      password <- lookInput "password"
      return (username, password)
  checkAuth errorHandler = do
      d <- getData myRqDataA
      case d of
          Nothing -> errorHandler
          Just a | isValid a -> mzero
          Just a | otherwise -> errorHandler
getData :: (ServerMonad m, FromData a) => m (Maybe a)Source

An varient of getData that uses FromData to chose your RqData for you. The example from getData becomes:

   myRqData = do
      username <- lookInput "username"
      password <- lookInput "password"
      return (username, password)
   instance FromData (String,String) where
      fromData = myRqData
   checkAuth errorHandler = do
      d <- getData'
      case d of
          Nothing -> errorHandler
          Just a | isValid a -> mzero
          Just a | otherwise -> errorHandler
require :: (MonadIO m, MonadPlus m) => IO (Maybe a) -> (a -> m r) -> m rSource
Run an IO action and, if it returns Just, pass it to the second argument.
requireM :: (MonadTrans t, Monad m, MonadPlus (t m)) => m (Maybe a) -> (a -> t m r) -> t m rSource
A varient of require that can run in any monad, not just IO
basicAuthSource
:: (WebMonad Response m, ServerMonad m, FilterMonad Response m, MonadPlus m)
=> Stringthe realm name
-> Map String Stringthe username password map
-> m athe part to guard
-> m a
a simple HTTP basic authentication guard
uriRest :: ServerMonad m => (String -> m a) -> m aSource
grabs the rest of the URL (dirs + query) and passes it to your handler
flatten :: (ToMessage a, Functor f) => f a -> f ResponseSource
flatten turns your arbitrary m a and converts it too a m Response with toResponse
localContext :: Monad m => (WebT m a -> WebT m' a) -> ServerPartT m a -> ServerPartT m' aSource
This is kinda like a very oddly shaped mapServerPartT or mapWebT You probably want one or the other of those.
proxying
proxyServe :: (MonadIO m, WebMonad Response m, ServerMonad m, MonadPlus m, FilterMonad Response m) => [String] -> m ResponseSource

proxyServe is for creating ServerPartT's that proxy. The sole argument [String] is a list of allowed domains for proxying. This matches the domain part of the request and the wildcard * can be used. E.g.

  • "*" to match anything.
  • "*.example.com" to match anything under example.com
  • "example.com" to match just example.com

TODO: annoyingly enough, this method eventually calls escape, so any headers you set won't be used, and the computation immediatly ends.

rproxyServeSource
:: MonadIO m
=> StringdefaultHost
-> [(String, String)]map to look up hostname mappings. For the reverse proxy
-> ServerPartT m Responsethe result is a ServerPartT that will reverse proxy for you.

This is a reverse proxy implementation. see unrproxify

TODO: this would be more useful if it didn't call escape, just like proxyServe'

unknown
debugFilter :: (MonadIO m, Show a) => ServerPartT m a -> ServerPartT m aSource
what is this for, exactly? I don't understand why Show a is even in the context This appears to do nothing at all.
applyRequest :: (ToMessage a, Monad m, Functor m) => ServerPartT m a -> Request -> Either (m Response) bSource
again, why is this useful?
Parsing input and cookies
lookInput :: String -> RqData InputSource
Useful inside the RqData monad. Gets the named input parameter (either from a POST or a GET)
lookBS :: String -> RqData ByteStringSource
Gets the named input parameter as a lazy byte string
look :: String -> RqData StringSource
Gets the named input as a String
lookCookie :: String -> RqData CookieSource
Gets the named cookie the cookie name is case insensitive
lookCookieValue :: String -> RqData StringSource
gets the named cookie as a string
readCookieValue :: Read a => String -> RqData aSource
gets the named cookie as the requested Read type
lookRead :: Read a => String -> RqData aSource
like look, but Reads for you.
lookPairs :: RqData [(String, String)]Source
gets all the input parameters, and converts them to a string
XSLT
xsltSource
:: (MonadIO m, MonadPlus m, ToMessage r)
=> XSLTCmdXSLT preprocessor. Usually xsltproc or saxon.
-> XSLPathPath to xslt stylesheet.
-> m rAffected ServerParts.
-> m Response
Use cmd to transform XML against xslPath. This function only acts if the content-type is application/xml.
doXslt :: MonadIO m => XSLTCmd -> XSLPath -> Response -> m ResponseSource
Error Handlng
errorHandlerSP :: (Monad m, Error e) => (Request -> e -> WebT m a) -> ServerPartT (ErrorT e m) a -> ServerPartT m aSource

This ServerPart modifier enables the use of throwError and catchError inside the WebT actions, by adding the ErrorT monad transformer to the stack.

You can wrap the complete second argument to simpleHTTP in this function.

simpleErrorHandler :: Monad m => String -> ServerPartT m ResponseSource

An example error Handler to be used with spUnWrapErrorT, which returns the error message as a plain text message to the browser.

Another possibility is to store the error message, e.g. as a FlashMsg, and then redirect the user somewhere.

spUnwrapErrorT :: Monad m => (e -> ServerPartT m a) -> Request -> UnWebT (ErrorT e m) a -> UnWebT m aSource

This is a for use with mapServerPartT' It it unwraps the interior monad for use with simpleHTTP. If you have a ServerPartT (ErrorT e m) a, this will convert that monad into a ServerPartT m a. Used with mapServerPartT' to allow throwError and catchError inside your monad. Eg.

   simpleHTTP conf $ mapServerPartT' (spUnWrapErrorT failurePart)  $ myPart `catchError` errorPart

Note that failurePart will only be run if errorPart threw an error so it doesn't have to be very complex.

Output Validation
setValidator :: (Response -> IO Response) -> Response -> ResponseSource

Set the validator which should be used for this particular Response when validation is enabled.

Calling this function does not enable validation. That can only be done by enabling the validation in the Conf that is passed to simpleHTTP.

You do not need to call this function if the validator set in Conf does what you want already.

Example: (use noopValidator instead of the default supplied by validateConf)

  simpleHTTP validateConf . anyRequest $ ok . setValidator noopValidator =<< htmlPage

See also: validateConf, wdgHTMLValidator, noopValidator, lazyProcValidator

setValidatorSP :: (Monad m, ToMessage r) => (Response -> IO Response) -> m r -> m ResponseSource

ServerPart version of setValidator

Example: (Set validator to noopValidator)

   simpleHTTP validateConf $ setValidatorSP noopValidator (dir ajax ... )

See also: setValidator

validateConf :: ConfSource

This extends nullConf by enabling validation and setting wdgHTMLValidator as the default validator for text/html.

Example:

  simpleHTTP validateConf . anyRequest $ ok htmlPage
runValidator :: (Response -> IO Response) -> Response -> IO ResponseSource

Actually perform the validation on a Response

Run the validator specified in the Response. If none is provide use the supplied default instead.

Note: This function will run validation unconditionally. You probably want setValidator or validateConf.

wdgHTMLValidator :: (MonadIO m, ToMessage r) => r -> m ResponseSource

Validate text/html content with WDG HTML Validator.

This function expects the executable to be named validate and it must be in the default PATH.

See also: setValidator, validateConf, lazyProcValidator

noopValidator :: Response -> IO ResponseSource

A validator which always succeeds.

Useful for selectively disabling validation. For example, if you are sending down HTML fragments to an AJAX application and the default validator only understands complete documents.

lazyProcValidatorSource
:: FilePathname of executable
-> [String]arguements to pass to the executable
-> Maybe FilePathoptional path to working directory
-> Maybe [(String, String)]optional environment (otherwise inherit)
-> Maybe ByteString -> Boolcontent-type filter
-> ResponseResponse to validate
-> IO Response

Validate the Response using an external application.

If the external application returns 0, the original response is returned unmodified. If the external application returns non-zero, a Response containing the error messages and original response body is returned instead.

This function also takes a predicate filter which is applied to the content-type of the response. The filter will only be applied if the predicate returns true.

NOTE: This function requirse the use of -threaded to avoid blocking. However, you probably need that for Happstack anyway.

See also: wdgHTMLValidator

Produced by Haddock version 2.6.1