happstack-lite-7.3.8: Happstack minus the useless stuff
Safe HaskellNone
LanguageHaskell2010

Happstack.Lite

Description

happstack-lite provides a simplied introduction to happstack-server. (Nearly) all the functions in happstack-lite are simple re-exports from the happstack-server package. happstack-lite offers two key advantages over happstack-server:

  1. it only contains the most commonly used functions, gathered in one convenient location.
  2. the type signatures have been simplified to remove most references to type classes, monad transformers, and other potentially confusing type signatures.

The beautiful part about happstack-lite is that because it merely re-exports functions and types from happstack-server it is possible to gradually import extra functionality from happstack-server on an as-need basis.

There is a brief introduction to happstack-lite located here:

http://www.happstack.com/C/ViewPage/9

More detailed examples and information can be found in the Happstack Crash Course:

http://www.happstack.com/docs/crashcourse/index.html

The Happstack Crash Course is written against happstack-server but the behavior of the functions available in happstack-lite is almost identical.

Synopsis

Core Types

data Request #

an HTTP request

Instances

Instances details
Show Request 
Instance details

Defined in Happstack.Server.Internal.Types

HasHeaders Request 
Instance details

Defined in Happstack.Server.Internal.Types

data Response #

an HTTP Response

Instances

Instances details
Show Response 
Instance details

Defined in Happstack.Server.Internal.Types

ToMessage Response 
Instance details

Defined in Happstack.Server.Response

Error Response 
Instance details

Defined in Happstack.Server.Internal.Types

HasHeaders Response 
Instance details

Defined in Happstack.Server.Internal.Types

Monad m => FilterMonad Response (ServerPartT m) 
Instance details

Defined in Happstack.Server.Internal.Monads

Monad m => FilterMonad Response (WebT m) 
Instance details

Defined in Happstack.Server.Internal.Monads

Methods

setFilter :: (Response -> Response) -> WebT m () #

composeFilter :: (Response -> Response) -> WebT m () #

getFilter :: WebT m b -> WebT m (b, Response -> Response) #

Monad m => WebMonad Response (ServerPartT m) 
Instance details

Defined in Happstack.Server.Internal.Monads

Methods

finishWith :: Response -> ServerPartT m b #

Monad m => WebMonad Response (WebT m) 
Instance details

Defined in Happstack.Server.Internal.Monads

Methods

finishWith :: Response -> WebT m b #

type ServerPart a = ServerPartT IO a #

An alias for ServerPartT IO

Starting the Server

data ServerConfig Source #

configuration to be used with serve function

Constructors

ServerConfig 

Fields

defaultServerConfig :: ServerConfig Source #

a reasonable default ServerConfig

ServerConfig { port      = 8000
             , ramQuota  = 1 * 10^6
             , diskQuota = 20 * 10^6
             , tmpDir    = "/tmp/"
             }

serve Source #

Arguments

:: Maybe ServerConfig

if Nothing, then use defaultServerConfig

-> ServerPart Response

request handler

-> IO () 

start the server and handle requests using the supplied ServerPart

Routing an Incoming Request

method :: MatchMethod method => method -> ServerPart () Source #

Guard against the request method

Example:

handler :: ServerPart Response
handler =
    do method [GET, HEAD]
       ...

data Method #

HTTP request method

Instances

Instances details
Eq Method 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

(==) :: Method -> Method -> Bool #

(/=) :: Method -> Method -> Bool #

Data Method 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Method -> c Method #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Method #

toConstr :: Method -> Constr #

dataTypeOf :: Method -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Method) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Method) #

gmapT :: (forall b. Data b => b -> b) -> Method -> Method #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Method -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Method -> r #

gmapQ :: (forall d. Data d => d -> u) -> Method -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Method -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Method -> m Method #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Method -> m Method #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Method -> m Method #

Ord Method 
Instance details

Defined in Happstack.Server.Internal.Types

Read Method 
Instance details

Defined in Happstack.Server.Internal.Types

Show Method 
Instance details

Defined in Happstack.Server.Internal.Types

MatchMethod Method 
Instance details

Defined in Happstack.Server.Routing

Methods

matchMethod :: Method -> Method -> Bool #

MatchMethod [Method] 
Instance details

Defined in Happstack.Server.Routing

Methods

matchMethod :: [Method] -> Method -> Bool #

MatchMethod (Method -> Bool) 
Instance details

Defined in Happstack.Server.Routing

Methods

matchMethod :: (Method -> Bool) -> Method -> Bool #

class MatchMethod m where #

instances of this class provide a variety of ways to match on the Request method.

Examples:

method GET                  -- match GET or HEAD
method [GET, POST]          -- match GET, HEAD or POST
method HEAD                 -- match HEAD /but not/ GET
method (== GET)             -- match GET or HEAD
method (not . (==) DELETE)  -- match any method except DELETE
method ()                   -- match any method

As you can see, GET implies that HEAD should match as well. This is to make it harder to write an application that uses HTTP incorrectly. Happstack handles HEAD requests automatically, but we still need to make sure our handlers don't mismatch or a HEAD will result in a 404.

If you must, you can still do something like this to match GET without HEAD:

guardRq ((== GET) . rqMethod)

Methods

matchMethod :: m -> Method -> Bool #

Instances

Instances details
MatchMethod () 
Instance details

Defined in Happstack.Server.Routing

Methods

matchMethod :: () -> Method -> Bool #

MatchMethod Method 
Instance details

Defined in Happstack.Server.Routing

Methods

matchMethod :: Method -> Method -> Bool #

MatchMethod [Method] 
Instance details

Defined in Happstack.Server.Routing

Methods

matchMethod :: [Method] -> Method -> Bool #

MatchMethod (Method -> Bool) 
Instance details

Defined in Happstack.Server.Routing

Methods

matchMethod :: (Method -> Bool) -> Method -> Bool #

dir :: String -> ServerPart a -> ServerPart a Source #

Pop a path element and run the supplied handler if it matches the given string.

handler :: ServerPart Response
handler = dir "foo" $ dir "bar" $ subHandler

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

path :: FromReqURI a => (a -> ServerPart b) -> ServerPart b Source #

Pop a path element and parse it using the fromReqURI in the FromReqURI class.

class FromReqURI a where #

This class is used by path to parse a path component into a value.

The instances for number types (Int, Float, etc) use readM to parse the path component.

The instance for String, on the other hand, returns the unmodified path component.

See the following section of the Happstack Crash Course for detailed instructions using and extending FromReqURI:

http://www.happstack.com/docs/crashcourse/RouteFilters.html#FromReqURI

Methods

fromReqURI :: String -> Maybe a #

Instances

Instances details
FromReqURI Bool 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Char 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Double 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Float 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Int 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Int #

FromReqURI Int8 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Int16 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Int32 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Int64 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Integer 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Word 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Word8 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Word16 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Word32 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Word64 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI String 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Text 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Text 
Instance details

Defined in Happstack.Server.Internal.Types

nullDir :: ServerPart () Source #

guard which only succeeds if there are no remaining path segments

Often used if you want to explicitly assign a route for /

guardRq :: (Request -> Bool) -> ServerPart () Source #

Guard using an arbitrary function on the Request.

Creating a Response

class ToMessage a where #

toResponse will convert a value into a Response body, set the content-type, and set the default response code for that type.

happstack-server Example:

main = simpleHTTP nullConf $ toResponse "hello, world!"

will generate a Response with the content-type text/plain, the response code 200 OK, and the body: hello, world!.

simpleHTTP will call toResponse automatically, so the above can be shortened to:

main = simpleHTTP nullConf $ "hello, world!"

happstack-lite Example:

main = serve Nothing $ toResponse "hello, world!"

Minimal definition: toMessage (and usually toContentType).

Minimal complete definition

Nothing

Instances

Instances details
ToMessage Integer 
Instance details

Defined in Happstack.Server.Response

ToMessage () 
Instance details

Defined in Happstack.Server.Response

ToMessage String 
Instance details

Defined in Happstack.Server.Response

ToMessage ByteString 
Instance details

Defined in Happstack.Server.Response

ToMessage ByteString 
Instance details

Defined in Happstack.Server.Response

ToMessage Text 
Instance details

Defined in Happstack.Server.Response

ToMessage Text 
Instance details

Defined in Happstack.Server.Response

ToMessage Html 
Instance details

Defined in Happstack.Server.Response

ToMessage Response 
Instance details

Defined in Happstack.Server.Response

ToMessage Html 
Instance details

Defined in Happstack.Server.Response

ToMessage Html 
Instance details

Defined in Happstack.Server.Response

ToMessage a => ToMessage (Maybe a) 
Instance details

Defined in Happstack.Server.Response

toResponseBS Source #

Arguments

:: ByteString

content-type

-> ByteString

response body

-> Response 

A 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 without requiring an instance declaration.

example:

import Data.ByteString.Char8 as C
import Data.ByteString.Lazy.Char8 as L
import Happstack.Lite

main = serve Nothing $ ok $ toResponseBS (C.pack "text/plain") (L.pack "hello, world")

(note: pack and pack only work for ascii. For unicode strings you would need to use utf8-string, text, or something similar to create a valid ByteString).

Setting the Response Code

ok :: a -> ServerPart a Source #

Respond with 200 OK.

main = serve Nothing $ ok "Everything is OK"

internalServerError :: a -> ServerPart a Source #

Respond with 500 Internal Server Error.

main = serve Nothing $ internalServerError "Sorry, there was an internal server error."

unauthorized :: a -> ServerPart a Source #

Respond with 401 Unauthorized.

main = serve Nothing $ unauthorized "You are not authorized."

notFound :: a -> ServerPart a Source #

Respond with 404 Not Found.

main = serve Nothing $ notFound "What you are looking for has not been found."

seeOther :: ToSURI uri => uri -> a -> ServerPart a Source #

Respond with 303 See Other.

main = serve Nothing $ seeOther "http://example.org/" "What you are looking for is now at http://example.org/"

NOTE: The second argument of seeOther is the message body which will sent to the browser. According to the HTTP 1.1 spec,

the entity of the response SHOULD contain a short hypertext note with a hyperlink to the new URI(s).

This is because pre-HTTP/1.1 user agents do not support 303. However, in practice you can probably just use "" as the second argument.

setResponseCode Source #

Arguments

:: Int

response code

-> ServerPart () 

Set an arbitrary return code in your response.

A filter for setting the response code. Generally you will use a helper function like ok or seeOther.

main = serve Nothing $ do setResponseCode 200
                          return "Everything is OK"

Looking up Request Parameters

lookBS :: String -> ServerPart ByteString Source #

Gets the first matching named input parameter as a lazy ByteString

Searches the QUERY_STRING followed by the Request body.

see also: lookBSs

lookBSs :: String -> ServerPart [ByteString] Source #

Gets all matches for the named input parameter as lazy ByteStrings

Searches the QUERY_STRING followed by the Request body.

see also: lookBS

lookText :: String -> ServerPart Text Source #

Gets the first matching named input parameter as a lazy Text

Searches the QUERY_STRING followed by the Request body.

This function assumes the underlying octets are UTF-8 encoded.

see also: lookTexts

lookTexts :: String -> ServerPart [Text] Source #

Gets all matches for the named input parameter as lazy Texts

Searches the QUERY_STRING followed by the Request body.

This function assumes the underlying octets are UTF-8 encoded.

see also: lookText

lookFile Source #

Arguments

:: String

name of input field to search for

-> ServerPart (FilePath, FilePath, ContentType)

(temporary file location, uploaded file name, content-type)

Gets the first matching named file

Files can only appear in the request body. Additionally, the form must set enctype="multipart/form-data".

This function returns a tuple consisting of:

  1. The temporary location of the uploaded file
  2. The local filename supplied by the browser
  3. The content-type supplied by the browser

NOTE: You must move the file from the temporary location before the Response is sent. The temporary files are automatically removed after the Response is sent.

data ContentType #

A MIME media type value. The Show instance is derived automatically. Use showContentType to obtain the standard string representation. See http://www.ietf.org/rfc/rfc2046.txt for more information about MIME media types.

Constructors

ContentType 

Fields

  • ctType :: String

    The top-level media type, the general type of the data. Common examples are "text", "image", "audio", "video", "multipart", and "application".

  • ctSubtype :: String

    The media subtype, the specific data format. Examples include "plain", "html", "jpeg", "form-data", etc.

  • ctParameters :: [(String, String)]

    Media type parameters. On common example is the charset parameter for the "text" top-level type, e.g. ("charset","ISO-8859-1").

Cookies

data Cookie #

a type for HTTP cookies. Usually created using mkCookie.

Instances

Instances details
Eq Cookie 
Instance details

Defined in Happstack.Server.Internal.Cookie

Methods

(==) :: Cookie -> Cookie -> Bool #

(/=) :: Cookie -> Cookie -> Bool #

Data Cookie 
Instance details

Defined in Happstack.Server.Internal.Cookie

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cookie -> c Cookie #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cookie #

toConstr :: Cookie -> Constr #

dataTypeOf :: Cookie -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cookie) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cookie) #

gmapT :: (forall b. Data b => b -> b) -> Cookie -> Cookie #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cookie -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cookie -> r #

gmapQ :: (forall d. Data d => d -> u) -> Cookie -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Cookie -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cookie -> m Cookie #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cookie -> m Cookie #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cookie -> m Cookie #

Read Cookie 
Instance details

Defined in Happstack.Server.Internal.Cookie

Show Cookie 
Instance details

Defined in Happstack.Server.Internal.Cookie

MonadReader RqEnv RqData 
Instance details

Defined in Happstack.Server.RqData

Methods

ask :: RqData RqEnv #

local :: (RqEnv -> RqEnv) -> RqData a -> RqData a #

reader :: (RqEnv -> a) -> RqData a #

data CookieLife #

Specify the lifetime of a cookie.

Note that we always set the max-age and expires headers because internet explorer does not honor max-age. You can specific MaxAge or Expires and the other will be calculated for you. Choose which ever one makes your life easiest.

Constructors

Session

session cookie - expires when browser is closed

MaxAge Int

life time of cookie in seconds

Expires UTCTime

cookie expiration date

Expired

cookie already expired

mkCookie #

Arguments

:: String

cookie name

-> String

cookie value

-> Cookie 

Creates a cookie with a default version of 1, empty domain, a path of "/", secure == False, httpOnly == False and sameSite == SameSiteNoValue

see also: addCookie

addCookies :: [(CookieLife, Cookie)] -> ServerPart () Source #

Add the list Cookie to the Response.

expireCookie :: String -> ServerPart () Source #

Expire the named cookie immediately and set the cookie value to ""

main = serve Nothing $
  do expireCookie "name"
     ok $ "The cookie has been expired."

lookCookieValue :: String -> ServerPart String Source #

gets the named cookie as a string

HTTP Headers

addHeaderM :: String -> String -> ServerPart () 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 :: String -> String -> ServerPart () 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.

getHeaderM :: String -> ServerPart (Maybe ByteString) Source #

Get a header out of the request.

File Serving

data Browsing #

Instances

Instances details
Enum Browsing 
Instance details

Defined in Happstack.Server.FileServe.BuildingBlocks

Eq Browsing 
Instance details

Defined in Happstack.Server.FileServe.BuildingBlocks

Data Browsing 
Instance details

Defined in Happstack.Server.FileServe.BuildingBlocks

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Browsing -> c Browsing #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Browsing #

toConstr :: Browsing -> Constr #

dataTypeOf :: Browsing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Browsing) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Browsing) #

gmapT :: (forall b. Data b => b -> b) -> Browsing -> Browsing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Browsing -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Browsing -> r #

gmapQ :: (forall d. Data d => d -> u) -> Browsing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Browsing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Browsing -> m Browsing #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Browsing -> m Browsing #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Browsing -> m Browsing #

Ord Browsing 
Instance details

Defined in Happstack.Server.FileServe.BuildingBlocks

Read Browsing 
Instance details

Defined in Happstack.Server.FileServe.BuildingBlocks

Show Browsing 
Instance details

Defined in Happstack.Server.FileServe.BuildingBlocks

serveDirectory Source #

Arguments

:: Browsing

allow directory browsing

-> [FilePath]

index file names, in case the requested path is a directory

-> FilePath

file/directory to serve

-> ServerPart Response 

Serve files and directories from a directory and its subdirectories using sendFile.

Usage:

serveDirectory EnableBrowsing ["index.html"] "path/to/files/on/disk"

If the requested path does not match a file or directory on the disk, then serveDirectory calls mzero.

If the requested path is a file then the file is served normally.

If the requested path is a directory, then the result depends on what the first two arguments to the function are.

The first argument controls whether directory browsing is enabled.

The second argument is a list of index files (such as index.html).

When a directory is requested, serveDirectory will first try to find one of the index files (in the order they are listed). If that fails, it will show a directory listing if EnableBrowsing is set, otherwise it will return forbidden "Directory index forbidden".

Here is an explicit list of all the possible outcomes when the argument is a (valid) directory:

DisableBrowsing, empty index file list

This will always return, forbidden "Directory index forbidden"

DisableBrowsing, non-empty index file list
  1. If an index file is found it will be shown.
  2. Otherwise returns, forbidden "Directory index forbidden"
EnableBrowsing, empty index file list

Always shows a directory index.

EnableBrowsing, non-empty index file list
  1. If an index file is found it will be shown
  2. Otherwise shows a directory index

see also: serveFile

serveFile Source #

Arguments

:: (FilePath -> ServerPart String)

function for determining content-type of file. Typically asContentType

-> FilePath

path to the file to serve

-> ServerPart Response 

Serve a single, specified file. The name of the file being served is specified explicity. It is not derived automatically from the Request url.

example 1:

Serve as a specific content-type:

serveFile (asContentType "image/jpeg") "/srv/data/image.jpg"

example 2:

Serve guessing the content-type from the extension:

serveFile (guessContentTypeM mimeTypes) "/srv/data/image.jpg"

If the specified path does not exist or is not a file, this function will return mzero.

WARNING: No security checks are performed.

NOTE: alias for serveFileUsing filePathSendFile

asContentType Source #

Arguments

:: String

the content-type to return

-> FilePath -> ServerPart String 

returns a specific content type, completely ignoring the FilePath argument.

Use this with serveFile if you want to explicitly specify the content-type.

see also: serveFile

type MimeMap = Map String String #

a Map from file extensions to content-types

example:

myMimeMap :: MimeMap
myMimeMap = Map.fromList [("gz","application/x-gzip"), ... ]

see also: mimeTypes

guessContentTypeM Source #

Arguments

:: MimeMap

map from file extensions to mime-types (usually mimeTypes)

-> FilePath -> ServerPart String 

try to guess the content-type of a file based on its extension

defaults to "application/octet-stream" if no match was found.

Useful as an argument to serveFile

see also: serveFile, mimeTypes

mimeTypes :: MimeMap #

Ready collection of common mime types. Except for the first two entries, the mappings come from http://svn.apache.org/viewvc/httpd/httpd/branches/2.4.x/docs/conf/mime.types?view=co

Other

class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where #

Monads that also support choice and failure.

Minimal complete definition

Nothing

Methods

mzero :: m a #

The identity of mplus. It should also satisfy the equations

mzero >>= f  =  mzero
v >> mzero   =  mzero

The default definition is

mzero = empty

mplus :: m a -> m a -> m a #

An associative operation. The default definition is

mplus = (<|>)

Instances

Instances details
MonadPlus []

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mzero :: [a] #

mplus :: [a] -> [a] -> [a] #

MonadPlus Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mzero :: Maybe a #

mplus :: Maybe a -> Maybe a -> Maybe a #

MonadPlus IO

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

mzero :: IO a #

mplus :: IO a -> IO a -> IO a #

MonadPlus ReadP

Since: base-2.1

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

mzero :: ReadP a #

mplus :: ReadP a -> ReadP a -> ReadP a #

MonadPlus RqData 
Instance details

Defined in Happstack.Server.RqData

Methods

mzero :: RqData a #

mplus :: RqData a -> RqData a -> RqData a #

MonadPlus P

Since: base-2.1

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

mzero :: P a #

mplus :: P a -> P a -> P a #

MonadPlus m => MonadPlus (ServerPartT m) 
Instance details

Defined in Happstack.Server.Internal.Monads

Methods

mzero :: ServerPartT m a #

mplus :: ServerPartT m a -> ServerPartT m a -> ServerPartT m a #

(Monad m, MonadPlus m) => MonadPlus (WebT m) 
Instance details

Defined in Happstack.Server.Internal.Monads

Methods

mzero :: WebT m a #

mplus :: WebT m a -> WebT m a -> WebT m a #

(Monad m, Error e) => MonadPlus (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

mzero :: ErrorT e m a #

mplus :: ErrorT e m a -> ErrorT e m a -> ErrorT e m a #

(Monoid e, Error e) => MonadPlus (ReaderError r e) 
Instance details

Defined in Happstack.Server.RqData

Methods

mzero :: ReaderError r e a #

mplus :: ReaderError r e a -> ReaderError r e a -> ReaderError r e a #

msum :: (Foldable t, MonadPlus m) => t (m a) -> m a #

The sum of a collection of actions, generalizing concat. As of base 4.8.0.0, msum is just asum, specialized to MonadPlus.