happstack-server-0.5.0.4: Web related tools and services.

Portabilityrequires mtl
Stabilityprovisional
Maintainerlemmih@vo.com

Happstack.Server.SimpleHTTP

Contents

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 be used if so desired.

So the general nature of simpleHTTP is just 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 to in a moment), picks the first handler that is willing to accept the request, and passes the request in to the handler. A simple hello world style Happstack 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 to 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 for which you want to demand authentication, 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

Documentation

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 mzero. This function always binds o IPv4 ports until Network module is fixed to support IPv6 in a portable way. Use simpleHTTPWithSocket with custom socket if you want different behaviour.

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. This function always binds to IPv4 ports until Network module is fixed to support IPv6 in a portable way. Use simpleHTTPWithSocket with custom socket if you want different behaviour.

simpleHTTP'' :: (ToMessage b, Monad m, Functor m) => ServerPartT m b -> Request -> m ResponseSource

Generate a result from a ServerPartT 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 $ simpleHTTPWithSocket 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

Like simpleHTTP' with a socket.

bindPort :: Conf -> IO SocketSource

Bind port and return the socket for simpleHTTPWithSocket. This function always binds to IPv4 ports until Network module is fixed to support IPv6 in a portable way.

parseConfig :: [String] -> Either [String] ConfSource

Parse command line options into a Conf.

ServerPartT

newtype ServerPartT m a Source

ServerPartT is a container for processing requests and returning results.

Constructors

ServerPartT 

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 et = do
      eitherV <- runErrorT et
      return $ case eitherV of
          Left err -> Just (Left $ toResponse $ "Catastrophic failure " ++ show err
                           , Set $ Dual $ Endo $ \r -> r{rsCode = 500})
          Right x -> 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 variant 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).

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 

Instances

MonadTrans WebT 
MonadError e m => MonadError e (WebT m) 
MonadReader r m => MonadReader r (WebT m) 
MonadState st m => MonadState st (WebT m) 
MonadWriter w m => MonadWriter w (WebT m) 
Monad m => WebMonad Response (WebT m) 
Monad m => FilterMonad Response (WebT m) 
Monad m => Monad (WebT m) 
Functor m => Functor (WebT m) 
Monad m => MonadPlus (WebT m) 
(Monad m, Functor m) => Applicative (WebT m) 
MonadIO m => MonadIO (WebT m) 
Monad m => Monoid (WebT m a) 

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"/

class ToMessage a whereSource

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.

Minimal definition: toMessage.

toResponseBSSource

Arguments

:: ByteString

content-type

-> ByteString

response body

-> Response 

low-level function to build a Response from a content-type and a ByteString

Creates a Response in a manner similar to the ToMessage class, but with out requiring an instance declaration.

Manipulating requests

class FromData a whereSource

Useful for withData and getData' implement this on your preferred type to use those functions.

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

Instances

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: 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.

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 summarizing 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 

Instances

newtype FilterT a m b Source

Constructors

FilterT 

Fields

unFilterT :: WriterT (FilterFun a) m b
 

Instances

Monad m => FilterMonad a (FilterT a m) 
MonadTrans (FilterT a) 
Monad m => Monad (FilterT a m) 
Functor m => Functor (FilterT a m) 
MonadIO m => MonadIO (FilterT a m) 

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.

addCookie :: FilterMonad Response m => Seconds -> Cookie -> m ()Source

Add the cookie with a timeout to the response.

addCookies :: FilterMonad Response m => [(Seconds, Cookie)] -> m ()Source

Add the list of cookie timeout pairs to the response.

expireCookie :: FilterMonad Response m => String -> m ()Source

Expire the cookie immediately.

addHeaderM :: FilterMonad Response m => String -> String -> m ()Source

Add 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

Set 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

Arguments

:: CalendarTime

mod-time for the Response (MUST NOT be later than server's time of message origination)

-> Request

incoming request (used to check for if-modified-since)

-> Response

Response to send if there are modifications

-> Response 

Honor an if-modified-since header in a 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.

modifyResponse :: FilterMonad a m => (a -> a) -> m ()Source

Deprecated: use composeFilter.

setResponseCode :: FilterMonad Response m => Int -> m ()Source

Set the return code in your response.

resp :: FilterMonad Response m => Int -> b -> m bSource

Same as setResponseCode status >> return val.

Respond Codes

ok :: FilterMonad Response m => a -> m aSource

Respond with 200 OK.

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.

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.

The path element can not contain '/'. See also dirs.

dirs :: (ServerMonad m, MonadPlus m) => FilePath -> m a -> m aSource

Guard against a FilePath. Unlike dir the FilePath may contain '/'. If the guard succeeds, the matched elements will be popped from the directory stack.

 dirs "foo/bar" $ ...

See also: dir.

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 is 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

Pop any path element and ignore 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 withData, but you pass in a RqData monad for reading.

getDataFn :: ServerMonad m => RqData a -> m (Maybe a)Source

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 variant 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 variant of require that can run in any monad, not just IO.

basicAuthSource

Arguments

:: (WebMonad Response m, ServerMonad m, FilterMonad Response m, MonadPlus m) 
=> String

the realm name

-> Map String String

the username password map

-> m a

the part to guard

-> m a 

A simple HTTP basic authentication guard.

uriRest :: ServerMonad m => (String -> m a) -> m aSource

Grab 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 ServerPartTs 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

Arguments

:: MonadIO m 
=> String

defaultHost

-> [(String, String)]

map to look up hostname mappings. For the reverse proxy

-> ServerPartT m Response

the 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 Deprecated: This function appears to do nothing at all. If it use it, let us know why.

applyRequest :: (ToMessage a, Monad m, Functor m) => ServerPartT m a -> Request -> Either (m Response) bSource

Again, why is this useful? Deprecated: No idea why this function would be useful. If you use it, please tell us.

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 request).

lookBS :: String -> RqData ByteStringSource

Get the named input parameter as a ByteString.

look :: String -> RqData StringSource

Get the named input as a String.

lookCookie :: String -> RqData CookieSource

Get the named cookie. The cookie name is case insensitive.

lookCookieValue :: String -> RqData StringSource

Get the named cookie as a String.

readCookieValue :: Read a => String -> RqData aSource

Get 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

Get all the input parameters and convert them to a String.

XSLT

xsltSource

Arguments

:: (MonadIO m, MonadPlus m, ToMessage r) 
=> XSLTCmd

XSLT preprocessor. Usually xsltproc or saxon.

-> XSLPath

Path to xslt stylesheet.

-> m r

Affected ServerParts.

-> m Response 

Use cmd to transform XML against xslPath. This function only acts if the content-type is application/xml.

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" ... )

validateConf :: ConfSource

Extend 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

Arguments

:: FilePath

name of executable

-> [String]

arguements to pass to the executable

-> Maybe FilePath

optional path to working directory

-> Maybe [(String, String)]

optional environment (otherwise inherit)

-> (Maybe ByteString -> Bool)

content-type filter

-> Response

Response 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.