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

Safe HaskellNone

Happstack.Server.Monads

Contents

Description

This module provides four classes and some related functions which provide ServerPartT with much of its web-centric behavior.

  1. ServerMonad provides access to the HTTP Request
  2. FilterMonad provides the ability to apply filters and transformations to a Response
  3. WebMonad provides a way to escape a computation early and return a Response
  4. HasRqData which provides access to the decoded QUERY_STRING and request body/form data

Synopsis

ServerPartT

type ServerPart a = ServerPartT IO aSource

An alias for ServerPartT IO

Happstack class

class (ServerMonad m, WebMonad Response m, FilterMonad Response m, MonadIO m, MonadPlus m, HasRqData m, Monad m, Functor m, Applicative m, Alternative m) => Happstack m Source

A class alias for all the classes a standard server monad (such as ServerPartT) is expected to have instances for. This allows you to keep your type signatures shorter and easier to understand.

Instances

(Functor m, Monad m, MonadPlus m, MonadIO m) => Happstack (ServerPartT m) 
(Happstack m, Error e) => Happstack (ErrorT e m) 
Happstack m => Happstack (ReaderT r m) 
Happstack m => Happstack (StateT s m) 
(Happstack m, Monoid w) => Happstack (WriterT w m) 
(Happstack m, Monoid w) => Happstack (RWST r w s m) 

ServerMonad

class Monad m => ServerMonad m whereSource

The ServerMonad class provides methods for reading or locally modifying the Request. It is essentially a specialized version of the MonadReader class. Providing the unique names, askRq and localRq makes it easier to use ServerPartT and ReaderT together.

Methods

askRq :: m RequestSource

localRq :: (Request -> Request) -> m a -> m aSource

mapServerPartT :: (UnWebT m a -> UnWebT n b) -> ServerPartT m a -> ServerPartT n bSource

Apply a function to transform the inner monad of ServerPartT m.

Often used when transforming a monad with ServerPartT, since simpleHTTP requires a ServerPartT IO a. Refer to UnWebT 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
                           , filterFun $ \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).

type UnWebT m a = m (Maybe (Either Response a, FilterFun Response))Source

UnWebT is almost exclusively used with mapServerPartT. If you are not using mapServerPartT then you do not need to wrap your head around this type. If you are -- the type is not as complex as it first appears.

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

filterFun :: (a -> a) -> FilterFun aSource

turn a function into a FilterFun. Primarily used with mapServerPartT

FilterMonad

class Monad m => FilterMonad a m | m -> a whereSource

A set of functions for manipulating filters.

ServerPartT implements FilterMonad Response so these methods are the fundamental ways of manipulating Response values.

Methods

setFilter :: (a -> a) -> m ()Source

Ignores all previous alterations to your filter

As an example:

 do
   composeFilter f
   setFilter g
   return "Hello World"

The setFilter g will cause the first composeFilter f 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

Retrieves the filter from the environment.

Instances

Monad m => FilterMonad Response (WebT m) 
Monad m => FilterMonad Response (ServerPartT m) 
(Error e, FilterMonad a m) => FilterMonad a (ErrorT e m) 
(FilterMonad res m, Monoid w) => FilterMonad res (WriterT w m) 
FilterMonad res m => FilterMonad res (StateT s m) 
FilterMonad res m => FilterMonad res (ReaderT r m) 
Monad m => FilterMonad a (FilterT a m) 
(FilterMonad res m, Monoid w) => FilterMonad res (RWST r w s m) 

ignoreFilters :: FilterMonad a m => m ()Source

Resets all your filters. An alias for setFilter id.

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.

getHeaderM :: ServerMonad m => String -> m (Maybe ByteString)Source

Get a header out of the request.

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.

neverExpires :: FilterMonad Response m => m ()Source

Set a far-future Expires header. Useful for static resources. If the browser has the resource cached, no extra request is spent.

WebMonad

class Monad m => WebMonad a m | m -> a whereSource

WebMonad provides a means to end the current computation and return a Response 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 accommodate this.

see also: escape and escape'

Methods

finishWithSource

Arguments

:: a

value to return (For ServerPart, a will always be the type Response)

-> m b 

Instances

Monad m => WebMonad Response (WebT m) 
Monad m => WebMonad Response (ServerPartT m) 
(Error e, WebMonad a m) => WebMonad a (ErrorT e m) 
(WebMonad a m, Monoid w) => WebMonad a (WriterT w m) 
WebMonad a m => WebMonad a (StateT s m) 
WebMonad a m => WebMonad a (ReaderT r m) 
(WebMonad a m, Monoid w) => WebMonad a (RWST r w s m) 

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.

MonadPlus helpers

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.