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:
- look :: (Functor m, Monad m, HasRqData m) => String -> m String
- looks :: (Functor m, Monad m, HasRqData m) => String -> m [String]
- lookBS :: (Functor m, Monad m, HasRqData m) => String -> m ByteString
- lookBSs :: (Functor m, Monad m, HasRqData m) => String -> m [ByteString]
- lookRead :: (Functor m, Monad m, HasRqData m, Read a) => String -> m a
- lookReads :: (Functor m, Monad m, HasRqData m, Read a) => String -> m [a]
- lookFile :: (Monad m, HasRqData m) => String -> m (FilePath, FilePath, ContentType)
- lookPairs :: (Monad m, HasRqData m) => m [(String, Either FilePath String)]
- lookPairsBS :: (Monad m, HasRqData m) => m [(String, Either FilePath ByteString)]
- lookCookie :: (Monad m, HasRqData m) => String -> m Cookie
- lookCookieValue :: (Functor m, Monad m, HasRqData m) => String -> m String
- readCookieValue :: (Functor m, Monad m, HasRqData m, Read a) => String -> m a
- lookInput :: (Monad m, HasRqData m) => String -> m Input
- lookInputs :: (Monad m, HasRqData m) => String -> m [Input]
- body :: HasRqData m => m a -> m a
- queryString :: HasRqData m => m a -> m a
- checkRq :: (Monad m, HasRqData m) => m a -> (a -> Either String b) -> m b
- checkRqM :: (Monad m, HasRqData m) => m a -> (a -> m (Either String b)) -> m b
- readRq :: Read a => String -> String -> Either String a
- decodeBody :: (ServerMonad m, MonadPlus m, MonadIO m) => BodyPolicy -> m ()
- data BodyPolicy = BodyPolicy {}
- defaultBodyPolicy :: FilePath -> Int64 -> Int64 -> Int64 -> BodyPolicy
- data RqData a
- mapRqData :: (Either (Errors String) a -> Either (Errors String) b) -> RqData a -> RqData b
- newtype Errors a = Errors {
- unErrors :: [a]
- getDataFn :: (HasRqData m, ServerMonad m, MonadIO m) => RqData a -> m (Either [String] a)
- withDataFn :: (HasRqData m, MonadIO m, MonadPlus m, ServerMonad m) => RqData a -> (a -> m r) -> m r
- class FromData a where
- getData :: (HasRqData m, MonadIO m, ServerMonad m, FromData a) => m (Either [String] a)
- withData :: (HasRqData m, MonadIO m, FromData a, MonadPlus m, ServerMonad m) => (a -> m r) -> m r
- type RqEnv = ([(String, Input)], [(String, Input)], [(String, Cookie)])
- class HasRqData m where
- askRqEnv :: m RqEnv
- localRqEnv :: (RqEnv -> RqEnv) -> m a -> m a
- rqDataError :: Errors String -> m a
Looking up keys
Form Values and Query Parameters
look :: (Functor m, Monad m, HasRqData m) => String -> m StringSource
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
lookBS :: (Functor m, Monad m, HasRqData m) => String -> m ByteStringSource
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 ByteString
s
Searches the QUERY_STRING followed by the Request body.
see also: lookBS
:: (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:
- The temporary location of the uploaded file
- The local filename supplied by the browser
- 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.
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 CookieSource
Gets the named cookie the cookie name is case insensitive
lookCookieValue :: (Functor m, Monad m, HasRqData m) => String -> m StringSource
gets the named cookie as a string
readCookieValue :: (Functor m, Monad m, HasRqData m, Read a) => String -> m aSource
gets the named cookie as the requested Read type
low-level
lookInput :: (Monad m, HasRqData m) => String -> m InputSource
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 aSource
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 aSource
limit the scope to the QUERY_STRING
handler :: ServerPart Response handler = do foo <- queryString $ look "foo" ok $ toResponse $ "foo = " ++ foo
Validation and Parsing
checkRq :: (Monad m, HasRqData m) => m a -> (a -> Either String b) -> m bSource
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:
- Parsing a
String
into another type - 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 bSource
like checkRq
but the check function can be monadic
Handling POST/PUT Requests
decodeBody :: (ServerMonad m, MonadPlus m, MonadIO m) => BodyPolicy -> m ()Source
The POST/PUT 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 POST/PUT 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
:: FilePath | temporary directory for file uploads |
-> Int64 | maximum bytes for files uploaded in this |
-> Int64 | maximum bytes for all non-file values in the |
-> Int64 | maximum bytes of overhead for headers in |
-> BodyPolicy |
create a BodyPolicy
for use with decodeBody
RqData Monad & Error Reporting
An applicative functor and monad for looking up key/value pairs in the QUERY_STRING, Request body, and cookies.
a list of errors
Using RqData with ServerMonad
:: (HasRqData m, ServerMonad m, MonadIO m) | |
=> RqData a |
|
-> m (Either [String] 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 or PUT.
withDataFn :: (HasRqData m, MonadIO m, MonadPlus m, ServerMonad m) => RqData a -> (a -> m r) -> m rSource
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 or PUT.
getData :: (HasRqData m, MonadIO 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 or PUT.
withData :: (HasRqData m, MonadIO m, FromData a, MonadPlus m, ServerMonad m) => (a -> m r) -> m rSource
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 or PUT.