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

Safe HaskellNone
LanguageHaskell98

Happstack.Server.RqData

Contents

Description

Functions for extracting values from the query string, form data, cookies, etc.

For in-depth documentation see the following section of the Happstack Crash Course:

http://happstack.com/docs/crashcourse/RqData.html

Synopsis

Looking up keys

Form Values and Query Parameters

look :: (Functor m, Monad m, HasRqData m) => String -> m String Source

Gets the first matching named input parameter as a String

Searches the QUERY_STRING followed by the Request body.

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

Example:

handler :: ServerPart Response
handler =
     do foo <- look "foo"
        ok $ toResponse $ "foo = " ++ foo

see also: looks, lookBS, and lookBSs

looks :: (Functor m, Monad m, HasRqData m) => String -> m [String] Source

Gets all matches for the named input parameter as Strings

Searches the QUERY_STRING followed by the Request body.

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

see also: look and lookBSs

lookText :: (Functor m, Monad m, HasRqData m) => String -> m 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, look, looks, lookBS, and lookBSs

lookText' :: (Functor m, Monad m, HasRqData m) => String -> m Text Source

Gets the first matching named input parameter as a strict Text

Searches the QUERY_STRING followed by the Request body.

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

see also: lookTexts, look, looks, lookBS, and lookBSs

lookTexts :: (Functor m, Monad m, HasRqData m) => String -> m [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, looks and lookBSs

lookTexts' :: (Functor m, Monad m, HasRqData m) => String -> m [Text] Source

Gets all matches for the named input parameter as strict Texts

Searches the QUERY_STRING followed by the Request body.

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

see also: lookText', looks and lookBSs

lookBS :: (Functor m, Monad m, HasRqData m) => String -> m 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 :: (Functor m, Monad m, HasRqData m) => String -> m [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

lookRead :: (Functor m, Monad m, HasRqData m, FromReqURI a) => String -> m a Source

Gets the first matching named input parameter and decodes it using Read

Searches the QUERY_STRING followed by the Request body.

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

see also: lookReads

lookReads :: (Functor m, Monad m, HasRqData m, FromReqURI a) => String -> m [a] Source

Gets all matches for the named input parameter and decodes them using Read

Searches the QUERY_STRING followed by the Request body.

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

see also: lookReads

lookFile Source

Arguments

:: (Monad m, HasRqData m) 
=> String

name of input field to search for

-> m (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

If the user does not supply a file in the html form input field, the behaviour will depend upon the browser. Most browsers will send a 0-length file with an empty file name, so checking that (2) is not empty is usually sufficient to ensure the field has been filled.

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.

lookPairs :: (Monad m, HasRqData m) => m [(String, Either FilePath String)] Source

gets all the input parameters, and converts them to a String

The results will contain the QUERY_STRING followed by the Request body.

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

see also: lookPairsBS

lookPairsBS :: (Monad m, HasRqData m) => m [(String, Either FilePath ByteString)] Source

gets all the input parameters

The results will contain the QUERY_STRING followed by the Request body.

see also: lookPairs

Cookies

lookCookie :: (Monad m, HasRqData m) => String -> m Cookie Source

Gets the named cookie the cookie name is case insensitive

lookCookieValue :: (Functor m, Monad m, HasRqData m) => String -> m String Source

gets the named cookie as a string

readCookieValue :: (Functor m, Monad m, HasRqData m, FromReqURI a) => String -> m a Source

gets the named cookie as the requested Read type

low-level

lookInput :: (Monad m, HasRqData m) => String -> m Input Source

Gets the first matching named input parameter

Searches the QUERY_STRING followed by the Request body.

see also: lookInputs

lookInputs :: (Monad m, HasRqData m) => String -> m [Input] Source

Gets all matches for the named input parameter

Searches the QUERY_STRING followed by the Request body.

see also: lookInput

Filters

body :: HasRqData m => m a -> m a Source

limit the scope to the Request body

handler :: ServerPart Response
handler =
    do foo <- body $ look "foo"
       ok $ toResponse $ "foo = " ++ foo

queryString :: HasRqData m => m a -> m a Source

limit the scope to the QUERY_STRING

handler :: ServerPart Response
handler =
    do foo <- queryString $ look "foo"
       ok $ toResponse $ "foo = " ++ foo

bytestring :: HasRqData m => m a -> m a Source

limit the scope to Inputs which produce a ByteString (aka, not a file)

Validation and Parsing

checkRq :: (Monad m, HasRqData m) => m a -> (a -> Either String b) -> m b Source

convert or validate a value

This is similar to fmap except that the function can fail by returning Left and an error message. The error will be propagated by calling rqDataError.

This function is useful for a number of things including:

  1. Parsing a String into another type
  2. Checking that a value meets some requirements (for example, that is an Int between 1 and 10).

Example usage at:

http://happstack.com/docs/crashcourse/RqData.html#rqdatacheckrq

checkRqM :: (Monad m, HasRqData m) => m a -> (a -> m (Either String b)) -> m b Source

like checkRq but the check function can be monadic

readRq Source

Arguments

:: FromReqURI a 
=> String

name of key (only used for error reporting)

-> String

String to read

-> Either String a

Left on error, Right on success

use fromReqURI to convert a String to a value of type a

look "key" `checkRq` (readRq "key")

use with checkRq

unsafeReadRq Source

Arguments

:: Read a 
=> String

name of key (only used for error reporting)

-> String

String to read

-> Either String a

Left on error, Right on success

use read to convert a String to a value of type a

look "key" `checkRq` (unsafeReadRq "key")

use with checkRq

NOTE: This function is marked unsafe because some Read instances are vulnerable to attacks that attempt to create an out of memory condition. For example:

read "1e10000000000000" :: Integer

see also: readRq

Handling POST/PUT Requests

decodeBody :: (ServerMonad m, MonadPlus m, MonadIO m, FilterMonad Response m, WebMonad Response m) => BodyPolicy -> m () Source

The body of a Request is not received or decoded unless this function is invoked.

It is an error to try to use the look functions for a Request with out first calling this function.

It is ok to call decodeBody at the beginning of every request:

main = simpleHTTP nullConf $
          do decodeBody (defaultBodyPolicy "/tmp/" 4096 4096 4096)
             handlers

You can achieve finer granularity quotas by calling decodeBody with different values in different handlers.

Only the first call to decodeBody will have any effect. Calling it a second time, even with different quota values, will do nothing.

Body Policy

data BodyPolicy Source

Constructors

BodyPolicy 

Fields

inputWorker :: Int64 -> Int64 -> Int64 -> InputWorker
 
maxDisk :: Int64

maximum bytes for files uploaded in this Request

maxRAM :: Int64

maximum bytes for all non-file values in the Request body

maxHeader :: Int64

maximum bytes of overhead for headers in multipart/form-data

defaultBodyPolicy Source

Arguments

:: FilePath

temporary directory for file uploads

-> Int64

maximum bytes for files uploaded in this Request

-> Int64

maximum bytes for all non-file values in the Request body

-> Int64

maximum bytes of overhead for headers in multipart/form-data

-> BodyPolicy 

create a BodyPolicy for use with decodeBody

RqData Monad & Error Reporting

data RqData a Source

An applicative functor and monad for looking up key/value pairs in the QUERY_STRING, Request body, and cookies.

mapRqData :: (Either (Errors String) a -> Either (Errors String) b) -> RqData a -> RqData b Source

transform the result of 'RqData a'.

This is similar to fmap except it also allows you to modify the Errors not just a.

newtype Errors a Source

a list of errors

Constructors

Errors 

Fields

unErrors :: [a]
 

Instances

Using RqData with ServerMonad

getDataFn Source

Arguments

:: (HasRqData m, ServerMonad m) 
=> RqData a

RqData monad to evaluate

-> m (Either [String] a)

return Left errors or Right a

run RqData in a ServerMonad.

Example: a simple GET or POST variable based authentication guard. It handles the request with errorHandler if authentication fails.

 data AuthCredentials = AuthCredentials { username :: String,  password :: String }

 isValid :: AuthCredentials -> Bool
 isValid = const True

 myRqData :: RqData AuthCredentials
 myRqData = do
    username <- look "username"
    password <- look "password"
    return (AuthCredentials username password)

 checkAuth :: (String -> ServerPart Response) -> ServerPart Response
 checkAuth errorHandler = do
    d <- getDataFn myRqData
    case d of
        (Left e) -> errorHandler (unlines e)
        (Right a) | isValid a -> mzero
        (Right a) | otherwise -> errorHandler "invalid"

NOTE: you must call decodeBody prior to calling this function if the request method is POST, PUT, PATCH, etc.

withDataFn :: (HasRqData m, MonadPlus m, ServerMonad m) => RqData a -> (a -> m r) -> m r Source

similar to getDataFn, except it calls a sub-handler on success or mzero on failure.

NOTE: you must call decodeBody prior to calling this function if the request method is POST, PUT, PATCH, etc.

class FromData a where Source

Used by withData and getData. Make your preferred data type an instance of FromData to use those functions.

Methods

fromData :: RqData a Source

Instances

FromData a => FromData (Maybe a) Source 
(FromData a, FromData b) => FromData (a, b) Source 
(FromData a, FromData b, FromData c) => FromData (a, b, c) Source 
(FromData a, FromData b, FromData c, FromData d) => FromData (a, b, c, d) Source 

getData :: (HasRqData m, ServerMonad m, FromData a) => m (Either [String] a) Source

A variant of getDataFn that uses FromData to chose your RqData for you. The example from getData becomes:

 data AuthCredentials = AuthCredentials { username :: String,  password :: String }

 isValid :: AuthCredentials -> Bool
 isValid = const True

 myRqData :: RqData AuthCredentials
 myRqData = do
    username <- look "username"
    password <- look "password"
    return (AuthCredentials username password)

 instance FromData AuthCredentials where
    fromData = myRqData

 checkAuth :: (String -> ServerPart Response) -> ServerPart Response
 checkAuth errorHandler = do
    d <- getData
    case d of
        (Left e) -> errorHandler (unlines e)
        (Right a) | isValid a -> mzero
        (Right a) | otherwise -> errorHandler "invalid"

NOTE: you must call decodeBody prior to calling this function if the request method is POST, PUT, PATCH, etc.

withData :: (HasRqData m, FromData a, MonadPlus m, ServerMonad m) => (a -> m r) -> m r Source

similar to getData except it calls a subhandler on success or mzero on failure.

NOTE: you must call decodeBody prior to calling this function if the request method is POST, PUT, PATCH, etc.

HasRqData class

type RqEnv = ([(String, Input)], Maybe [(String, Input)], [(String, Cookie)]) Source

the environment used to lookup query parameters. It consists of the triple: (query string inputs, body inputs, cookie inputs)

class HasRqData m where Source

A class for monads which contain a RqEnv

Methods

askRqEnv :: m RqEnv Source

localRqEnv :: (RqEnv -> RqEnv) -> m a -> m a Source

rqDataError :: Errors String -> m a Source

lift some Errors into RqData