Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains the core type definitions, class instances, and functions
for HTTP as well as the Snap
monad, which is used for web handlers.
- data Snap a
- runSnap :: Snap a -> (ByteString -> IO ()) -> ((Int -> Int) -> IO ()) -> Request -> IO (Request, Response)
- class (Monad m, MonadIO m, MonadBaseControl IO m, MonadPlus m, Functor m, Applicative m, Alternative m) => MonadSnap m where
- data NoHandlerException = NoHandlerException String
- bracketSnap :: IO a -> (a -> IO b) -> (a -> Snap c) -> Snap c
- finishWith :: MonadSnap m => Response -> m a
- catchFinishWith :: Snap a -> Snap (Either Response a)
- pass :: MonadSnap m => m a
- type EscapeHttpHandler = ((Int -> Int) -> IO ()) -> InputStream ByteString -> OutputStream Builder -> IO ()
- data EscapeSnap
- escapeHttp :: MonadSnap m => EscapeHttpHandler -> m ()
- terminateConnection :: (Exception e, MonadSnap m) => e -> m a
- method :: MonadSnap m => Method -> m a -> m a
- methods :: MonadSnap m => [Method] -> m a -> m a
- path :: MonadSnap m => ByteString -> m a -> m a
- pathArg :: (Readable a, MonadSnap m) => (a -> m b) -> m b
- dir :: MonadSnap m => ByteString -> m a -> m a
- ifTop :: MonadSnap m => m a -> m a
- route :: MonadSnap m => [(ByteString, m a)] -> m a
- routeLocal :: MonadSnap m => [(ByteString, m a)] -> m a
- getRequest :: MonadSnap m => m Request
- getsRequest :: MonadSnap m => (Request -> a) -> m a
- getResponse :: MonadSnap m => m Response
- getsResponse :: MonadSnap m => (Response -> a) -> m a
- putRequest :: MonadSnap m => Request -> m ()
- putResponse :: MonadSnap m => Response -> m ()
- modifyRequest :: MonadSnap m => (Request -> Request) -> m ()
- modifyResponse :: MonadSnap m => (Response -> Response) -> m ()
- localRequest :: MonadSnap m => (Request -> Request) -> m a -> m a
- withRequest :: MonadSnap m => (Request -> m a) -> m a
- withResponse :: MonadSnap m => (Response -> m a) -> m a
- logError :: MonadSnap m => ByteString -> m ()
- runRequestBody :: MonadSnap m => (InputStream ByteString -> IO a) -> m a
- readRequestBody :: MonadSnap m => Word64 -> m ByteString
- transformRequestBody :: (InputStream ByteString -> IO (InputStream ByteString)) -> Snap ()
- data Request
- data Response
- data Headers
- class HasHeaders a where
- type Params = Map ByteString [ByteString]
- data Method
- data Cookie = Cookie {
- cookieName :: !ByteString
- cookieValue :: !ByteString
- cookieExpires :: !(Maybe UTCTime)
- cookieDomain :: !(Maybe ByteString)
- cookiePath :: !(Maybe ByteString)
- cookieSecure :: !Bool
- cookieHttpOnly :: !Bool
- type HttpVersion = (Int, Int)
- addHeader :: HasHeaders a => CI ByteString -> ByteString -> a -> a
- setHeader :: HasHeaders a => CI ByteString -> ByteString -> a -> a
- getHeader :: HasHeaders a => CI ByteString -> a -> Maybe ByteString
- listHeaders :: HasHeaders a => a -> [(CI ByteString, ByteString)]
- deleteHeader :: HasHeaders a => CI ByteString -> a -> a
- ipHeaderFilter :: MonadSnap m => m ()
- ipHeaderFilter' :: MonadSnap m => CI ByteString -> m ()
- rqHeaders :: Request -> Headers
- rqHostName :: Request -> ByteString
- rqClientAddr :: Request -> ByteString
- rqClientPort :: Request -> Int
- rqServerAddr :: Request -> ByteString
- rqServerPort :: Request -> Int
- rqLocalHostname :: Request -> ByteString
- rqIsSecure :: Request -> Bool
- rqContentLength :: Request -> Maybe Word64
- rqMethod :: Request -> Method
- rqVersion :: Request -> HttpVersion
- rqCookies :: Request -> [Cookie]
- rqPathInfo :: Request -> ByteString
- rqContextPath :: Request -> ByteString
- rqURI :: Request -> ByteString
- rqQueryString :: Request -> ByteString
- rqParams :: Request -> Params
- rqQueryParams :: Request -> Params
- rqPostParams :: Request -> Params
- rqParam :: ByteString -> Request -> Maybe [ByteString]
- rqPostParam :: ByteString -> Request -> Maybe [ByteString]
- rqQueryParam :: ByteString -> Request -> Maybe [ByteString]
- getParam :: MonadSnap m => ByteString -> m (Maybe ByteString)
- getPostParam :: MonadSnap m => ByteString -> m (Maybe ByteString)
- getQueryParam :: MonadSnap m => ByteString -> m (Maybe ByteString)
- getParams :: MonadSnap m => m Params
- getPostParams :: MonadSnap m => m Params
- getQueryParams :: MonadSnap m => m Params
- rqModifyParams :: (Params -> Params) -> Request -> Request
- rqSetParam :: ByteString -> [ByteString] -> Request -> Request
- rqRemoteAddr :: Request -> ByteString
- rqRemotePort :: Request -> Int
- emptyResponse :: Response
- setResponseCode :: Int -> Response -> Response
- setResponseStatus :: Int -> ByteString -> Response -> Response
- rspStatus :: Response -> Int
- rspStatusReason :: Response -> ByteString
- setContentType :: ByteString -> Response -> Response
- addResponseCookie :: Cookie -> Response -> Response
- getResponseCookie :: ByteString -> Response -> Maybe Cookie
- getResponseCookies :: Response -> [Cookie]
- deleteResponseCookie :: ByteString -> Response -> Response
- modifyResponseCookie :: ByteString -> (Cookie -> Cookie) -> Response -> Response
- expireCookie :: MonadSnap m => Cookie -> m ()
- getCookie :: MonadSnap m => ByteString -> m (Maybe Cookie)
- readCookie :: (MonadSnap m, Readable a) => ByteString -> m a
- setContentLength :: Word64 -> Response -> Response
- clearContentLength :: Response -> Response
- redirect :: MonadSnap m => ByteString -> m a
- redirect' :: MonadSnap m => ByteString -> Int -> m a
- setResponseBody :: (OutputStream Builder -> IO (OutputStream Builder)) -> Response -> Response
- modifyResponseBody :: ((OutputStream Builder -> IO (OutputStream Builder)) -> OutputStream Builder -> IO (OutputStream Builder)) -> Response -> Response
- addToOutput :: MonadSnap m => (OutputStream Builder -> IO (OutputStream Builder)) -> m ()
- writeBuilder :: MonadSnap m => Builder -> m ()
- writeBS :: MonadSnap m => ByteString -> m ()
- writeLazyText :: MonadSnap m => Text -> m ()
- writeText :: MonadSnap m => Text -> m ()
- writeLBS :: MonadSnap m => ByteString -> m ()
- sendFile :: MonadSnap m => FilePath -> m ()
- sendFilePartial :: MonadSnap m => FilePath -> (Word64, Word64) -> m ()
- setTimeout :: MonadSnap m => Int -> m ()
- extendTimeout :: MonadSnap m => Int -> m ()
- modifyTimeout :: MonadSnap m => (Int -> Int) -> m ()
- getTimeoutModifier :: MonadSnap m => m ((Int -> Int) -> IO ())
- formatHttpTime :: CTime -> IO ByteString
- parseHttpTime :: ByteString -> IO CTime
- parseUrlEncoded :: ByteString -> Map ByteString [ByteString]
- buildUrlEncoded :: Map ByteString [ByteString] -> Builder
- printUrlEncoded :: Map ByteString [ByteString] -> ByteString
- urlEncode :: ByteString -> ByteString
- urlEncodeBuilder :: ByteString -> Builder
- urlDecode :: ByteString -> Maybe ByteString
The Snap Monad
Snap
is the Monad
that user web handlers run in. Snap
gives you:
Stateful access to fetch or modify an HTTP
Request
.printRqContextPath :: Snap () printRqContextPath =
writeBS
.rqContextPath
=<<getRequest
Stateful access to fetch or modify an HTTP
Response
.printRspStatusReason :: Snap () printRspStatusReason =
writeBS
.rspStatusReason
=<<getResponse
Failure /
Alternative
/MonadPlus
semantics: aSnap
handler can choose not to handle a given request, usingempty
or its synonympass
, and you can try alternative handlers with the<|>
operator:a :: Snap String a =
pass
b :: Snap String b = return "foo" c :: Snap String c = a<|>
b -- try running a, if it fails then try bConvenience functions (
writeBS
,writeLBS
,writeText
,writeLazyText
,addToOutput
) for queueing output to be written to theResponse
, or for streaming to the response using io-streams:example :: (
OutputStream
Builder
-> IO (OutputStream
Builder
)) -> Snap () example streamProc = dowriteBS
"I'm a strict bytestring"writeLBS
"I'm a lazy bytestring"writeText
"I'm strict text"addToOutput
streamProcEarly termination: if you call
finishWith
:a :: Snap () a = do
modifyResponse
$setResponseStatus
500 "Internal Server Error"writeBS
"500 error" r <-getResponse
finishWith
rthen any subsequent processing will be skipped and the supplied
Response
value will be returned fromrunSnap
as-is.Access to the
IO
monad through aMonadIO
instance:a :: Snap () a =
liftIO
fireTheMissilesThe ability to set or extend a timeout which will kill the handler thread after
N
seconds of inactivity (the default is 20 seconds):a :: Snap () a =
setTimeout
30Throw and catch exceptions using a
MonadBaseControl
instance:import Control.Exception.Lifted (
SomeException
,throwIO
,catch
) foo :: Snap () foo = bar `catch` (e::SomeException
) -> baz where bar =throwIO
FooExceptionLog a message to the error log:
foo :: Snap () foo =
logError
"grumble."
You may notice that most of the type signatures in this module contain a
(
typeclass constraint. MonadSnap
m) => ...MonadSnap
is a typeclass
which, in essence, says "you can get back to the Snap
monad from
here". Using MonadSnap
you can extend the Snap
monad with additional
functionality and still have access to most of the Snap
functions without
writing lift
everywhere. Instances are already
provided for most of the common monad transformers
(ReaderT
, WriterT
,
StateT
, etc.).
:: Snap a | Action to run. |
-> (ByteString -> IO ()) | Error logging action. |
-> ((Int -> Int) -> IO ()) | Timeout action. |
-> Request | HTTP request. |
-> IO (Request, Response) |
Runs a Snap
monad action.
This function is mostly intended for library writers; instead of invoking
runSnap
directly, use httpServe
or
runHandler
(for testing).
class (Monad m, MonadIO m, MonadBaseControl IO m, MonadPlus m, Functor m, Applicative m, Alternative m) => MonadSnap m where Source #
data NoHandlerException Source #
This exception is thrown if the handler you supply to runSnap
fails.
Functions for control flow and early termination
bracketSnap :: IO a -> (a -> IO b) -> (a -> Snap c) -> Snap c Source #
This function brackets a Snap action in resource acquisition and
release. This is provided because MonadCatchIO's bracket
function
doesn't work properly in the case of a short-circuit return from
the action being bracketed.
In order to prevent confusion regarding the effects of the aquisition and release actions on the Snap state, this function doesn't accept Snap actions for the acquire or release actions.
This function will run the release action in all cases where the acquire action succeeded. This includes the following behaviors from the bracketed Snap action.
- Normal completion
- Short-circuit completion, either from calling
fail
orfinishWith
- An exception being thrown.
Example:
ghci> :set -XOverloadedStrings
ghci> import qualified Data.Map as M
ghci> import qualified Snap.Test as T
ghci> let br = bracketSnap
(putStrLn "before") (const $ putStrLn "after")
ghci> T.runHandler (T.get "/" M.empty) (br $ const $ writeBS "OK")
before
after
HTTP/1.1 200 OK
server: Snap/test
date: Thu, 07 Aug 2014 18:41:50 GMT
OK
finishWith :: MonadSnap m => Response -> m a Source #
Short-circuits a Snap
monad action early, storing the given
Response
value in its state.
IMPORTANT: Be vary careful when using this with things like a DB library's
withTransaction
function or any other kind of setup/teardown block, as it
can prevent the cleanup from being called and result in resource leaks.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> import Control.Applicative ghci> let r = T.get "/" M.empty ghci> T.runHandler r ((ifTop
$writeBS
"TOP") <|>finishWith
emptyResponse
) HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 16:58:57 GMT TOP ghci> let r' = T.get "/foo/bar" M.empty ghci> T.runHandler r' ((ifTop
$writeBS
"TOP") <|>finishWith
emptyResponse
) HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 17:50:50 GMT
catchFinishWith :: Snap a -> Snap (Either Response a) Source #
Capture the flow of control in case a handler calls finishWith
.
WARNING: in the event of a call to transformRequestBody
it is possible
to violate HTTP protocol safety when using this function. If you call
catchFinishWith
it is suggested that you do not modify the body of the
Response
which was passed to the finishWith
call.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.ByteString.Char8 as B8 ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> import Control.Applicative ghci> let r = T.get "/foo/bar" M.empty ghci> let h = (ifTop
$writeBS
"TOP") <|>finishWith
emptyResponse
ghci> T.runHandler r (catchFinishWith
h >>=writeBS
. B8.pack . show) HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 18:35:42 GMT Left HTTP/1.1 200 OK
pass :: MonadSnap m => m a Source #
Fails out of a Snap
monad action. This is used to indicate
that you choose not to handle the given request within the given
handler.
Example:
ghci> :set -XOverloadedStrings
ghci> import qualified Data.Map as M
ghci> import qualified Snap.Test as T
ghci> let r = T.get "/foo/bar" M.empty
ghci> T.runHandler r pass
HTTP/1.1 404 Not Found
server: Snap/test
date: Thu, 07 Aug 2014 13:35:42 GMT
<!DOCTYPE html>
<html>
<head>
<title>Not found</title>
</head>
<body>
<code>No handler accepted "/foo/bar"/code
</body></html>
Escaping HTTP
type EscapeHttpHandler Source #
= ((Int -> Int) -> IO ()) | timeout modifier |
-> InputStream ByteString | socket read end |
-> OutputStream Builder | socket write end |
-> IO () |
Type of external handler passed to escapeHttp
.
data EscapeSnap Source #
Used internally to implement escapeHttp
.
escapeHttp :: MonadSnap m => EscapeHttpHandler -> m () Source #
Terminate the HTTP session and hand control to some external handler, escaping all further HTTP traffic.
The external handler takes three arguments: a function to modify the thread's timeout, and a read and a write ends to the socket.
terminateConnection :: (Exception e, MonadSnap m) => e -> m a Source #
Terminate the HTTP session with the given exception.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> import qualified Control.Exception as E ghci> let r = T.get "/foo/bar" M.empty ghci> T.runHandler r (terminateConnection $ E.AssertionFailed "Assertion failed!") *** Exception: <terminated: Assertion failed!>
Routing
method :: MonadSnap m => Method -> m a -> m a Source #
Runs a Snap
monad action only if the request's HTTP method matches
the given method.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/foo/bar" M.empty ghci> T.runHandler r (method
GET
$writeBS
"OK") HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 13:38:48 GMT OK ghci> T.runHandler r (method
POST
$writeBS
"OK") HTTP/1.1 404 Not Found ...
methods :: MonadSnap m => [Method] -> m a -> m a Source #
Runs a Snap
monad action only if the request's HTTP method matches
one of the given methods.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/foo/bar" M.empty ghci> T.runHandler r (methods
[GET
,POST
] $writeBS
"OK") HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 13:38:48 GMT OK ghci> T.runHandler r (methods
[POST
] $writeBS
"OK") HTTP/1.1 404 Not Found ...
:: MonadSnap m | |
=> ByteString | path to match against |
-> m a | handler to run |
-> m a |
Runs a Snap
monad action only for requests where rqPathInfo
is
exactly equal to the given string. If the path matches, locally sets
rqContextPath
to the old value of rqPathInfo
, sets rqPathInfo
="",
and runs the given handler.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> T.runHandler (T.get "/foo" M.empty) (path
"foo" $writeBS
"bar") HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 14:15:42 GMT bar ghci> T.runHandler (T.get "/foo" M.empty) (path
"bar" $writeBS
"baz") HTTP/1.1 404 Not Found ...
pathArg :: (Readable a, MonadSnap m) => (a -> m b) -> m b Source #
Runs a Snap
monad action only when the first path component is
successfully parsed as the argument to the supplied handler function.
Note that the path segment is url-decoded prior to being passed to fromBS
;
this is new as of snap-core 0.10.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/11/foo/bar" M.empty ghci> let f = (\i -> if i == 11 thenwriteBS
"11" elsewriteBS
"???") ghci> T.runHandler r (pathArg
f) HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 14:27:10 GMT 11 ghci> let r' = T.get "/foo/11/bar" M.empty ghci> T.runHandler r' (pathArg
f) HTTP/1.1 404 Not Found ...
:: MonadSnap m | |
=> ByteString | path component to match |
-> m a | handler to run |
-> m a |
Runs a Snap
monad action only when the rqPathInfo
of the request
starts with the given path. For example,
dir "foo" handler
Will fail if rqPathInfo
is not "/foo
" or "/foo/...
", and will
add "foo/"
to the handler's local rqContextPath
.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/foo/bar" M.empty ghci> T.runHandler r (dir
"foo" $writeBS
"OK") HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 14:52:24 GMT OK ghci> T.runHandler r (dir
"baz" $writeBS
"OK") HTTP/1.1 404 Not Found ...
ifTop :: MonadSnap m => m a -> m a Source #
Runs a Snap
monad action only when rqPathInfo
is empty.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/" M.empty ghci> T.runHandler r (ifTop
$writeBS
OK) HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 14:56:39 GMT OK ghci> let r' = T.get "/foo" M.empty ghci> T.runHandler r' (ifTop
$writeBS
"OK") HTTP/1.1 404 Not Found ...
route :: MonadSnap m => [(ByteString, m a)] -> m a Source #
A web handler which, given a mapping from URL entry points to web handlers, efficiently routes requests to the correct handler.
Usage
The URL entry points are given as relative paths, for example:
route [ ("foo/bar/quux", fooBarQuux) ]
If the URI of the incoming request is /foo/bar/quux
or
/foo/bar/quux/...anything...
then the request will be routed to
"fooBarQuux"
, with rqContextPath
set to "/foo/bar/quux/"
and
rqPathInfo
set to "...anything..."
.
A path component within an URL entry point beginning with a colon (":"
)
is treated as a variable capture; the corresponding path component within
the request URI will be entered into the rqParams
parameters mapping with
the given name. For instance, if the routes were:
route [ ("foo/:bar/baz", fooBazHandler) ]
Then a request for "/foo/saskatchewan/baz"
would be routed to
fooBazHandler
with a mapping for "bar" => "saskatchewan"
in its
parameters table.
Longer paths are matched first, and specific routes are matched before captures. That is, if given routes:
[ ("a", h1), ("a/b", h2), ("a/:x", h3) ]
a request for "/a/b"
will go to h2
, "/a/s"
for any s will go
to h3
, and "/a"
will go to h1
.
The following example matches "/article"
to an article index,
"/login"
to a login, and "/article/..."
to an article renderer.
route
[ ("article", renderIndex) , ("article/:id", renderArticle) , ("login",method
POST doLogin) ]
Note: URL decoding
A short note about URL decoding: path matching and variable capture are done
on decoded URLs, but the contents of rqContextPath
and rqPathInfo
will
contain the original encoded URL, i.e. what the user entered. For example,
in the following scenario:
route [ ("a b c d/", foo ) ]
A request for "/a+b+c+d
" will be sent to foo
with rqContextPath
set
to "a+b+c+d"
.
This behaviour changed as of Snap 0.6.1; previous versions had unspecified (and buggy!) semantics here.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as Map ghci> import qualified Data.ByteString.Char8 as B8 ghci> import Snap.Test ghci> :{ ghci| let handler = do r <-getRequest
ghci|writeBS
$ "rqContextPath: " <>rqContextPath
r <> "\n" ghci|writeBS
$ "rqPathInfo: " <>rqPathInfo
r <> "\n" ghci|writeBS
$ "rqParams: " <> (B8.pack . show $rqParams
r) ghci| :} ghci>runHandler
(get
"/foo/bar" "Map.empty") (route
[("foo", handler)]) HTTP/1.1 200 OK server: Snap/test date: Sat, 02 Aug 2014 05:16:59 GMT rqContextPath: /foo/ rqPathInfo: bar rqParams: fromList [] ghci>runHandler
(get
"/foo/bar" "Map.empty") (route
[("foo/:bar", handler)]) [...] rqContextPath: /foo/bar/ rqPathInfo: rqParams: fromList [("bar",["bar"])]
routeLocal :: MonadSnap m => [(ByteString, m a)] -> m a Source #
The routeLocal
function is the same as route
, except it doesn't
change the request's context path. This is useful if you want to route to a
particular handler but you want that handler to receive the rqPathInfo
as
it is.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Data.ByteString.Char8 as B8 ghci> import Snap.Test ghci> :{ ghci| let handler = do r <-getRequest
ghci|writeBS
$ "rqContextPath: " <>rqContextPath
r <> "\n" ghci|writeBS
$ "rqPathInfo: " <>rqPathInfo
r <> "\n" ghci|writeBS
$ "rqParams: " <> (B8.pack . show $rqParams
r) ghci| :} ghci>runHandler
(get
"/foo/bar" M.empty) (routeLocal
[("foo", handler)]) HTTP/1.1 200 OK server: Snap/test date: Sat, 02 Aug 2014 05:17:28 GMT rqContextPath: / rqPathInfo: foo/bar ghci>runHandler
(get
"/foo/bar" M.empty) (routeLocal
[("foo/:bar", handler)]) [...] rqContextPath: / rqPathInfo: foo/bar rqParams: fromList [("bar",["bar"])]
Access to state
getRequest :: MonadSnap m => m Request Source #
Grabs the Request
object out of the Snap
monad.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/foo/bar" M.empty ghci> T.runHandler r (writeBS
.rqURI
=<<getRequest
) HTTP/1.1 200 OK server: Snap/test date: Sat, 02 Aug 2014 07:51:54 GMT /foo/bar
getsRequest :: MonadSnap m => (Request -> a) -> m a Source #
Grabs something out of the Request
object, using the given projection
function. See gets
.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/foo/bar" M.empty ghci> T.runHandler r (writeBS
=<<getsRequest
rqURI
) HTTP/1.1 200 OK server: Snap/test date: Sat, 02 Aug 2014 07:51:54 GMT /foo/bar
getResponse :: MonadSnap m => m Response Source #
Grabs the Response
object out of the Snap
monad.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/foo/bar" M.empty ghci> T.runHandler r (writeBS
.rspStatusReason
=<<getResponse
) HTTP/1.1 200 OK server: Snap/test date: Sat, 02 Aug 2014 15:06:00 GMT OK
getsResponse :: MonadSnap m => (Response -> a) -> m a Source #
Grabs something out of the Response
object, using the given projection
function. See gets
.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/foo/bar" M.empty ghci> T.runHandler r (writeBS
=<<getsResponse
rspStatusReason
) HTTP/1.1 200 OK server: Snap/test date: Wed, 06 Aug 2014 13:35:45 GMT OK
putRequest :: MonadSnap m => Request -> m () Source #
Puts a new Request
object into the Snap
monad.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> :{ ghci| let hndlr = do rq <- T.buildRequest (T.get "/bar/foo" M.empty) ghci|putRequest
rq ghci| uri' <-getsRequest
rqURI
ghci|writeBS
uri' ghci| :} ghci> T.runHandler (T.get "/foo/bar" M.empty) hndlr HTTP/1.1 200 OK server: Snap/test date: Wed, 06 Aug 2014 15:13:46 GMT /bar/foo
putResponse :: MonadSnap m => Response -> m () Source #
Puts a new Response
object into the Snap
monad.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let rsp =setResponseCode
404emptyResponse
ghci> let req = T.get "/foo/bar" M.empty ghci> T.runHandler req (putResponse
rsp) HTTP/1.1 404 Not Found server: Snap/test date: Wed, 06 Aug 2014 13:59:58 GMT
modifyRequest :: MonadSnap m => (Request -> Request) -> m () Source #
Modifies the Request
object stored in a Snap
monad.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/foo/bar" M.empty ghci> r' <- T.buildRequest $ T.get "/bar/foo" M.empty ghci> T.runHandler r (modifyRequest
(const r') >>getsRequest
rqURI
>>=writeBS
) HTTP/1.1 200 OK server: Snap/test date: Wed, 06 Aug 2014 15:24:25 GMT /bar/foo
modifyResponse :: MonadSnap m => (Response -> Response) -> m () Source #
Modifes the Response
object stored in a Snap
monad.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/foo/bar" M.empty ghci> T.runHandler r (modifyResponse
$setResponseCode
404) HTTP/1.1 404 Not Found server: Snap/test date: Wed, 06 Aug 2014 15:27:11 GMT
localRequest :: MonadSnap m => (Request -> Request) -> m a -> m a Source #
Runs a Snap
action with a locally-modified Request
state
object. The Request
object in the Snap monad state after the call
to localRequest will be unchanged.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/foo/bar" M.empty ghci> r' <- T.buildRequest $ T.get "/bar/foo" M.empty ghci> let printRqURI =getsRequest
rqURI
>>=writeBS
>>writeBS
"\n" ghci> T.runHandler r (printRqURI >>localRequest
(const r') printRqURI) HTTP/1.1 200 OK server: Snap/test date: Wed, 06 Aug 2014 15:34:12 GMT /foo/bar /bar/foo
withRequest :: MonadSnap m => (Request -> m a) -> m a Source #
Fetches the Request
from state and hands it to the given action.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> import Control.Monad.IO.Class ghci> let r = T.get "/foo/bar" M.empty ghci> let h =withRequest
(\rq ->liftIO
(T.requestToString rq) >>=writeBS
) ghci> T.runHandler r h HTTP/1.1 200 OK server: Snap/test date: Wed, 06 Aug 2014 15:44:24 GMT GET /foo/bar HTTP/1.1 host: localhost
withResponse :: MonadSnap m => (Response -> m a) -> m a Source #
Fetches the Response
from state and hands it to the given action.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/foo/bar" M.empty ghci> T.runHandler r (withResponse
$writeBS
.rspStatusReason
) HTTP/1.1 200 OK server: Snap/test date: Wed, 06 Aug 2014 15:48:45 GMT OK
Logging
logError :: MonadSnap m => ByteString -> m () Source #
Log an error message in the Snap
monad.
Example:
ghci> import qualified Data.ByteString.Char8 as B8 ghci>runSnap
(logError
"fatal error!") (error
. B8.unpack) undefined undefined *** Exception: fatal error!
Grabbing/transforming request bodies
runRequestBody :: MonadSnap m => (InputStream ByteString -> IO a) -> m a Source #
Pass the request body stream to a consuming procedure, returning the result.
If the consuming procedure you pass in here throws an exception, Snap will
attempt to clear the rest of the unread request body (using
skipToEof
) before rethrowing the
exception. If you used terminateConnection
, however, Snap will give up and
immediately close the socket.
To prevent slowloris attacks, the connection will be also terminated if the input socket produces data too slowly (500 bytes per second is the default limit).
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.ByteString.Char8 as B8 ghci> import qualified Data.ByteString.Lazy as L ghci> import Data.Char (toUpper) ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> import qualified System.IO.Streams as Streams ghci> let r = T.put "/foo" "text/plain" "some text" ghci> :{ ghci| let f s = do u <- Streams.map (B8.map toUpper) s ghci| l <- Streams.toList u ghci| return $ L.fromChunks l ghci| :} ghci> T.runHandler r (runRequestBody
f >>=writeLBS
) HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 20:48:40 GMT SOME TEXT
:: MonadSnap m | |
=> Word64 | size of the largest request body we're willing
to accept. If a request body longer than this is
received, a |
-> m ByteString |
Returns the request body as a lazy bytestring. /Note that the request is not actually provided lazily!/
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.put "/foo" "text/plain" "some text" ghci> T.runHandler r (readRequestBody
2048 >>=writeLBS
) HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 20:08:44 GMT some text
Since: 0.6
:: (InputStream ByteString -> IO (InputStream ByteString)) | the |
-> Snap () |
Normally Snap is careful to ensure that the request body is fully
consumed after your web handler runs, but before the Response
body
is streamed out the socket. If you want to transform the request body into
some output in O(1) space, you should use this function.
Take care: in order for this to work, the HTTP client must be written with input-to-output streaming in mind.
Note that upon calling this function, response processing finishes early as
if you called finishWith
. Make sure you set any content types, headers,
cookies, etc. before you call this function.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.ByteString.Char8 as B8 ghci> import Data.Char (toUpper) ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> import qualified System.IO.Streams as Streams ghci> let r = T.put "/foo" "text/plain" "some text" ghci> let f = Streams.map (B8.map toUpper) ghci> T.runHandler r (transformRequestBody
f >>readRequestBody
2048 >>=writeLBS
) HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 20:30:15 GMT SOME TEXT
HTTP Datatypes and Functions
Contains all of the information about an incoming HTTP request.
Show Request Source # | |
HasHeaders Request Source # | |
Monad m => MonadState Request (RequestBuilder m) # | |
Represents an HTTP response.
A key-value map that represents a collection of HTTP header fields. Keys are case-insensitive.
class HasHeaders a where Source #
A typeclass for datatypes which contain HTTP headers.
type Params = Map ByteString [ByteString] Source #
A type alias for the HTTP parameters mapping. Each parameter
key maps to a list of ByteString
values; if a parameter is specified
multiple times (e.g.: "GET /foo?param=bar1¶m=bar2
"), looking up
"param
" in the mapping will give you ["bar1", "bar2"]
.
Enumerates the HTTP method values (see http://tools.ietf.org/html/rfc2068.html#section-5.1.1).
A datatype representing an HTTP cookie.
Cookie | |
|
type HttpVersion = (Int, Int) Source #
Represents a (major, minor) version of the HTTP protocol.
Headers
addHeader :: HasHeaders a => CI ByteString -> ByteString -> a -> a Source #
Adds a header key-value-pair to the HasHeaders
datatype. If a header
with the same name already exists, the new value is appended to the headers
list.
Example:
ghci> import qualified Snap.Types.Headers as H ghci>addHeader
Host "localhost" H.empty
H {unH = [("host","localhost")]} ghci>addHeader
Host "127.0.0.1" it H {unH = [("host","localhost,127.0.0.1")]}
setHeader :: HasHeaders a => CI ByteString -> ByteString -> a -> a Source #
Sets a header key-value-pair in a HasHeaders
datatype. If a header with
the same name already exists, it is overwritten with the new value.
Example:
ghci> import qualified Snap.Types.Headers as H ghci>setHeader
Host "localhost" H.empty
H {unH = [("host","localhost")]} ghci> setHeader Host "127.0.0.1" it H {unH = [("host","127.0.0.1")]}
getHeader :: HasHeaders a => CI ByteString -> a -> Maybe ByteString Source #
Gets a header value out of a HasHeaders
datatype.
Example:
ghci> import qualified Snap.Types.Headers as H ghci>getHeader
Host $setHeader
Host "localhost" H.empty
Just "localhost"
listHeaders :: HasHeaders a => a -> [(CI ByteString, ByteString)] Source #
Lists all the headers out of a HasHeaders
datatype. If many
headers came in with the same name, they will be catenated together.
Example:
ghci> import qualified Snap.Types.Headers as H ghci>listHeaders
$setHeader
Host "localhost" H.empty
[("host","localhost")]
deleteHeader :: HasHeaders a => CI ByteString -> a -> a Source #
Clears a header value from a HasHeaders
datatype.
Example:
ghci> import qualified Snap.Types.Headers as H ghci>deleteHeader
Host $setHeader
Host "localhost" H.empty
H {unH = []}
ipHeaderFilter :: MonadSnap m => m () Source #
Modifies the Request
in the state to set the rqRemoteAddr
field to the value in the X-Forwarded-For header. If the header is
not present, this action has no effect.
This action should be used only when working behind a reverse http proxy that sets the X-Forwarded-For header. This is the only way to ensure the value in the X-Forwarded-For header can be trusted.
This is provided as a filter so actions that require the remote address can get it in a uniform manner. It has specifically limited functionality to ensure that its transformation can be trusted, when used correctly.
ipHeaderFilter' :: MonadSnap m => CI ByteString -> m () Source #
Modifies the Request
in the state to set the rqRemoteAddr
field to the value from the header specified. If the header
specified is not present, this action has no effect.
This action should be used only when working behind a reverse http proxy that sets the header being looked at. This is the only way to ensure the value in the header can be trusted.
This is provided as a filter so actions that require the remote address can get it in a uniform manner. It has specifically limited functionality to ensure that its transformation can be trusted, when used correctly.
Requests
rqHostName :: Request -> ByteString Source #
The server name of the request, as it came in from the request's
Host:
header.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Snap.Test as T ghci> import qualified Data.Map as M ghci> :{ ghci| rq <- T.buildRequest $ do ghci| T.get "/foo/bar" M.empty ghci| T.setHeader "host" "example.com" ghci| :} ghci> rqHostName rq "example.com"
rqClientAddr :: Request -> ByteString Source #
rqClientPort :: Request -> Int Source #
rqServerAddr :: Request -> ByteString Source #
rqServerPort :: Request -> Int Source #
Returns the port number the HTTP server is listening on. This may be useless from the perspective of external requests, e.g. if the server is running behind a proxy.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Snap.Test as T ghci> import qualified Data.Map as M ghci> rqServerPort `fmap` T.buildRequest (T.get "/foo/bar" M.empty) 8080
rqLocalHostname :: Request -> ByteString Source #
Returns the HTTP server's idea of its local hostname, including
port. This is as configured with the Config
object at startup.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Snap.Test as T ghci> import qualified Data.Map as M ghci> rqLocalHostname `fmap` T.buildRequest (T.get "/foo/bar" M.empty) "localhost"
rqIsSecure :: Request -> Bool Source #
rqVersion :: Request -> HttpVersion Source #
rqPathInfo :: Request -> ByteString Source #
Handlers can be hung on a URI
"entry point"; this is called the
"context path". If a handler is hung on the context path
"/foo/"
, and you request "/foo/bar"
, the value of
rqPathInfo
will be "bar"
.
The following identity holds:
rqURI r == S.concat [ rqContextPath r , rqPathInfo r , let q = rqQueryString r in if S.null q then "" else S.append "?" q ]
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Snap.Test as T ghci> import qualified Data.Map as M ghci> rqPathInfo `fmap` T.buildRequest (T.get "/foo/bar" M.empty) "foo/bar"
rqContextPath :: Request -> ByteString Source #
The "context path" of the request; catenating rqContextPath
,
and rqPathInfo
should get you back to the original rqURI
(ignoring query strings). The rqContextPath
always begins and ends
with a slash ("/"
) character, and represents the path (relative
to your component/snaplet) you took to get to your handler.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Snap.Test as T ghci> import qualified Data.Map as M ghci> rqContextPath `fmap` T.buildRequest (T.get "/foo/bar" M.empty) "/"
rqURI :: Request -> ByteString Source #
rqQueryString :: Request -> ByteString Source #
rqParams :: Request -> Params Source #
Returns the parameters mapping for this Request
. "Parameters"
are automatically decoded from the URI's query string and POST
body
and entered into this mapping. The rqParams
value is thus a union of
rqQueryParams
and rqPostParams
.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Snap.Test as T ghci> import qualified Data.Map as M ghci> :{ ghci| rq <- T.buildRequest $ do ghci| T.postUrlEncoded "/foo/bar" $ M.fromList [("baz", ["qux"])] ghci| T.setQueryStringRaw "baz=quux" ghci| :} ghci> rqParams rq fromList [("baz",["qux","quux"])]
rqQueryParams :: Request -> Params Source #
The parameter mapping decoded from the URI's query string.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Snap.Test as T ghci> import qualified Data.Map as M ghci> :{ ghci| rq <- T.buildRequest $ do ghci| T.postUrlEncoded "/foo/bar" $ M.fromList [("baz", ["qux"])] ghci| T.setQueryStringRaw "baz=quux" ghci| :} ghci> rqQueryParams rq fromList [("baz",["quux"])]
rqPostParams :: Request -> Params Source #
The parameter mapping decoded from the POST body. Note that Snap
only auto-decodes POST request bodies when the request's
Content-Type
is application/x-www-form-urlencoded
.
For multipart/form-data
use handleFileUploads
to decode the POST request and fill this mapping.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Snap.Test as T ghci> import qualified Data.Map as M ghci> :{ ghci| rq <- T.buildRequest $ do ghci| T.postUrlEncoded "/foo/bar" $ M.fromList [("baz", ["qux"])] ghci| T.setQueryStringRaw "baz=quux" ghci| :} ghci> rqPostParams rq fromList [("baz",["qux"])]
:: ByteString | parameter name to look up |
-> Request | HTTP request |
-> Maybe [ByteString] |
Looks up the value(s) for the given named parameter. Parameters initially
come from the request's query string and any decoded POST body (if the
request's Content-Type
is application/x-www-form-urlencoded
).
Parameter values can be modified within handlers using "rqModifyParams".
Example:
ghci> :set -XOverloadedStrings
ghci> import qualified Snap.Test as T
ghci> import qualified Data.Map as M
ghci> :{
ghci| rq <- T.buildRequest $ do
ghci| T.postUrlEncoded "/foo/bar" $ M.fromList [("baz", ["qux"])]
ghci| T.setQueryStringRaw "baz=quux"
ghci| :}
ghci> rqParam
"baz" rq
Just ["qux","quux"]
:: ByteString | parameter name to look up |
-> Request | HTTP request |
-> Maybe [ByteString] |
Looks up the value(s) for the given named parameter in the POST parameters mapping.
Example:
ghci> :set -XOverloadedStrings
ghci> import qualified Snap.Test as T
ghci> import qualified Data.Map as M
ghci> :{
ghci| rq <- T.buildRequest $ do
ghci| T.postUrlEncoded "/foo/bar" $ M.fromList [("baz", ["qux"])]
ghci| T.setQueryStringRaw "baz=quux"
ghci| :}
ghci> rqPostParam
"baz" rq
Just ["qux"]
:: ByteString | parameter name to look up |
-> Request | HTTP request |
-> Maybe [ByteString] |
Looks up the value(s) for the given named parameter in the query parameters mapping.
Example:
ghci> :set -XOverloadedStrings
ghci> import qualified Snap.Test as T
ghci> import qualified Data.Map as M
ghci> :{
ghci| rq <- T.buildRequest $ do
ghci| T.postUrlEncoded "/foo/bar" $ M.fromList [("baz", ["qux"])]
ghci| T.setQueryStringRaw "baz=quux"
ghci| :}
ghci> rqQueryParam
"baz" rq
Just ["quux"]
:: MonadSnap m | |
=> ByteString | parameter name to look up |
-> m (Maybe ByteString) |
See rqParam
. Looks up a value for the given named parameter in the
Request
. If more than one value was entered for the given parameter name,
getParam
gloms the values together with
.intercalate
" "
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> import qualified Data.ByteString.Char8 as B8 ghci> let r = T.get "/foo/bar" $ M.fromList [("foo", ["bar"])] ghci> T.runHandler r (getParam
"foo" >>=writeBS
. B8.pack . show) HTTP/1.1 200 OK server: Snap/test date: Mon, 11 Aug 2014 12:57:20 GMT Just "bar"
:: MonadSnap m | |
=> ByteString | parameter name to look up |
-> m (Maybe ByteString) |
See rqPostParam
. Looks up a value for the given named parameter in the
POST form parameters mapping in Request
. If more than one value was
entered for the given parameter name, getPostParam
gloms the values
together with:
.intercalate
" "
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> import qualified Data.ByteString.Char8 as B8 ghci> let r = T.postUrlEncoded "/foo/bar" $ M.fromList [("foo", ["bar"])] ghci> T.runHandler r (getPostParam
"foo" >>=writeBS
. B8.pack . show) HTTP/1.1 200 OK server: Snap/test date: Mon, 11 Aug 2014 13:01:04 GMT Just "bar"
:: MonadSnap m | |
=> ByteString | parameter name to look up |
-> m (Maybe ByteString) |
See rqQueryParam
. Looks up a value for the given named parameter in the
query string parameters mapping in Request
. If more than one value was
entered for the given parameter name, getQueryParam
gloms the values
together with
.intercalate
" "
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> import qualified Data.ByteString.Char8 as B8 ghci> let r = T.postUrlEncoded "/foo/bar" M.empty >> T.setQueryStringRaw "foo=bar&foo=baz" ghci> T.runHandler r (getQueryParam
"foo" >>=writeBS
. B8.pack . show) HTTP/1.1 200 OK server: Snap/test date: Mon, 11 Aug 2014 13:06:50 GMT Just "bar baz"
getParams :: MonadSnap m => m Params Source #
See rqParams
. Convenience function to return Params
from the
Request
inside of a MonadSnap
instance.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> import qualified Data.ByteString.Char8 as B8 ghci> let r = T.get "/foo/bar" $ M.fromList [("foo", ["bar"])] ghci> T.runHandler r (getParams
>>=writeBS
. B8.pack . show) HTTP/1.1 200 OK server: Snap/test date: Mon, 11 Aug 2014 13:02:54 GMT fromList [("foo",["bar"])]
getPostParams :: MonadSnap m => m Params Source #
See rqParams
. Convenience function to return Params
from the
Request
inside of a MonadSnap
instance.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> import qualified Data.ByteString.Char8 as B8 ghci> let r = T.postUrlEncoded "/foo/bar" $ M.fromList [("foo", ["bar"])] ghci> T.runHandler r (getPostParams
>>=writeBS
. B8.pack . show) HTTP/1.1 200 OK server: Snap/test date: Mon, 11 Aug 2014 13:04:34 GMT fromList [("foo",["bar"])]
getQueryParams :: MonadSnap m => m Params Source #
See rqParams
. Convenience function to return Params
from the
Request
inside of a MonadSnap
instance.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> import qualified Data.ByteString.Char8 as B8 ghci> let r = T.postUrlEncoded "/foo/bar" M.empty >> T.setQueryStringRaw "foo=bar&foo=baz" ghci> T.runHandler r (getQueryParams
>>=writeBS
. B8.pack . show) HTTP/1.1 200 OK server: Snap/test date: Mon, 11 Aug 2014 13:10:17 GMT fromList [("foo",["bar","baz"])]
rqModifyParams :: (Params -> Params) -> Request -> Request Source #
Modifies the parameters mapping (which is a Map ByteString ByteString
)
in a Request
using the given function.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Snap.Test as T ghci> import qualified Data.Map as M ghci> :{ ghci| rq <- T.buildRequest $ do ghci| T.postUrlEncoded "/foo/bar" $ M.fromList [("baz", ["qux"])] ghci| T.setQueryStringRaw "baz=quux" ghci| :} ghci>rqParams
rq fromList [("baz",["qux","quux"])] ghci>rqParams
$rqModifyParams
(M.delete "baz") rq fromList []
:: ByteString | parameter name |
-> [ByteString] | parameter values |
-> Request | request |
-> Request |
Writes a key-value pair to the parameters mapping within the given request.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Snap.Test as T ghci> import qualified Data.Map as M ghci> :{ ghci| rq <- T.buildRequest $ do ghci| T.postUrlEncoded "/foo/bar" $ M.fromList [("baz", ["qux"])] ghci| T.setQueryStringRaw "baz=quux" ghci| :} ghci>rqParams
rq fromList [("baz",["qux","quux"])] ghci>rqParams
$rqSetParam
"baz" ["corge"] rq fromList [("baz", ["corge"])]
Deprecated functions
rqRemoteAddr :: Request -> ByteString Source #
Deprecated: (snap-core >= 1.0.0.0) please use rqClientAddr
, this will be removed in 1.1.*
See rqClientAddr
.
rqRemotePort :: Request -> Int Source #
Deprecated: (snap-core >= 1.0.0.0) please use rqClientPort
, this will be removed in 1.1.*
See rqClientPort
.
Responses
:: Int | HTTP response integer code |
-> ByteString | HTTP response explanation |
-> Response | Response to be modified |
-> Response |
Sets the HTTP response status. Note: normally you would use
setResponseCode
unless you needed a custom response explanation.
Example:
ghci> :set -XOverloadedStrings
ghci> setResponseStatus 500 "Internal Server Error" emptyResponse
HTTP/1.1 500 Internal Server Error
rspStatusReason :: Response -> ByteString Source #
setContentType :: ByteString -> Response -> Response Source #
Sets the Content-Type
in the Response
headers.
Example:
ghci> :set -XOverloadedStrings
ghci> setContentType "text/html" emptyResponse
HTTP/1.1 200 OK
content-type: text/html
Adds an HTTP Cookie
to Response
headers.
Example:
ghci> :set -XOverloadedStrings ghci> let cookie =Cookie
"name" "value" Nothing Nothing Nothing False False ghci>getResponseCookie
"name" $addResponseCookie
cookieemptyResponse
Just (Cookie {cookieName = "name", cookieValue = "value", ...})
:: ByteString | cookie name |
-> Response | response to query |
-> Maybe Cookie |
Gets an HTTP Cookie
with the given name from Response
headers.
Example:
ghci> :set -XOverloadedStrings ghci>getResponseCookie
"cookie-name"emptyResponse
Nothing
:: ByteString | cookie name |
-> Response | response to modify |
-> Response |
Deletes an HTTP Cookie
from the Response
headers. Please note
this does not necessarily erase the cookie from the client browser.
Example:
ghci> :set -XOverloadedStrings ghci> let cookie =Cookie
"name" "value" Nothing Nothing Nothing False False ghci> let rsp =addResponseCookie
cookieemptyResponse
ghci>getResponseCookie
"name" rsp Just (Cookie {cookieName = "name", cookieValue = "value", ...}) ghci>getResponseCookie
"name" $deleteResponseCookie
"name" rsp Nothing
:: ByteString | cookie name |
-> (Cookie -> Cookie) | modifier function |
-> Response | response to modify |
-> Response |
Modifies an HTTP Cookie
with given name in Response
headers.
Nothing will happen if a matching Cookie
can not be found in Response
.
Example:
ghci> :set -XOverloadedStrings ghci> import Data.Monoid ghci> let cookie =Cookie
"name" "value" Nothing Nothing Nothing False False ghci> let rsp =addResponseCookie
cookieemptyResponse
ghci>getResponseCookie
"name" rsp Just (Cookie {cookieName = "name", cookieValue = "value", ...}) ghci> let f ck@(Cookie
{ cookieName = name }) = ck { cookieName = name <> "'"} ghci> let rsp' =modifyResponseCookie
"name" f rsp ghci>getResponseCookie
"name'" rsp' Just (Cookie {cookieName = "name'", ...}) ghci>getResponseCookie
"name" rsp' Just (Cookie {cookieName = "name", ...})
expireCookie :: MonadSnap m => Cookie -> m () Source #
Expire given Cookie
in client's browser.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let r = T.get "/foo/bar" M.empty ghci> let cookie = Cookie "name" "" Nothing (Just "/subsite") Nothing True False ghci> T.runHandler r (expireCookie
cookie) HTTP/1.1 200 OK set-cookie: name=; path=/subsite; expires=Sat, 24 Dec 1994 06:28:16 GMT; Secure server: Snap/test date: Thu, 07 Aug 2014 12:21:27 GMT ghci> let cookie = Cookie "name" "value" Nothing Nothing Nothing False False ghci> let r2 = T.get "/foo/bar" M.empty >> T.addCookies [cookie] ghci> T.runHandler r (getCookie
"name" >>= maybe (return ())expireCookie
) HTTP/1.1 200 OK set-cookie: name=; expires=Sat, 24 Dec 1994 06:28:16 GMT server: Snap/test
getCookie :: MonadSnap m => ByteString -> m (Maybe Cookie) Source #
Gets the HTTP Cookie
with the specified name.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> import qualified Data.ByteString.Char8 as B8 ghci> let cookie =Cookie
"name" "value" Nothing Nothing Nothing False False ghci> let r = T.get "/foo/bar" M.empty >> T.addCookies [cookie] ghci> T.runHandler r (getCookie
"name" >>=writeBS
. B8.pack . show) HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 12:16:58 GMT Just (Cookie {cookieName = "name", cookieValue = "value", ...})
readCookie :: (MonadSnap m, Readable a) => ByteString -> m a Source #
Gets the HTTP Cookie
with the specified name and decodes it. If the
decoding fails, the handler calls pass.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci> let cookie =Cookie
"name" "value" Nothing Nothing Nothing False False ghci> let r = T.get "/foo/bar" M.empty >> T.addCookies [cookie] ghci> T.runHandler r (readCookie
"name" >>=writeBS
) HTTP/1.1 200 OK server: Snap/test date: Thu, 07 Aug 2014 12:20:09 GMT value
setContentLength :: Word64 -> Response -> Response Source #
A note here: if you want to set the Content-Length
for the response,
Snap forces you to do it with this function rather than by setting it in
the headers; the Content-Length
in the headers will be ignored.
The reason for this is that Snap needs to look up the value of
Content-Length
for each request, and looking the string value up in the
headers and parsing the number out of the text will be too expensive.
If you don't set a content length in your response, HTTP keep-alive will be
disabled for HTTP/1.0 clients, forcing a Connection: close
. For
HTTP/1.1 clients, Snap will switch to the chunked transfer encoding if
Content-Length
is not specified.
Example:
ghci> setContentLength 400 emptyResponse
HTTP/1.1 200 OK
Content-Length: 400
clearContentLength :: Response -> Response Source #
Removes any Content-Length
set in the Response
.
Example:
ghci> clearContentLength $setContentLength
400emptyResponse
HTTP/1.1 200 OK
redirect :: MonadSnap m => ByteString -> m a Source #
Performs a redirect by setting the Location
header to the given target
URL/path and the status code to 302 in the Response
object stored in a
Snap
monad. Note that the target URL is not validated in any way.
Consider using redirect'
instead, which allows you to choose the correct
status code.
Example:
ghci> :set -XOverloadedStrings
ghci> import qualified Data.Map as M
ghci> import qualified Snap.Test as T
ghci> let r = T.get "/foo/bar" M.empty
ghci> T.runHandler r (redirect
"http://snapframework.com")
HTTP/1.1 302 Found
content-length: 0
location: http://snapframework.com
server: Snap/test
date: Thu, 07 Aug 2014 08:52:11 GMT
Content-Length: 0
redirect' :: MonadSnap m => ByteString -> Int -> m a Source #
Performs a redirect by setting the Location
header to the given target
URL/path and the status code (should be one of 301, 302, 303 or 307) in the
Response
object stored in a Snap
monad. Note that the target URL is not
validated in any way.
Example:
ghci> :set -XOverloadedStrings
ghci> import qualified Data.Map as M
ghci> import qualified Snap.Test as T
ghci> let r = T.get "/foo/bar" M.empty
ghci> T.runHandler r (redirect'
"http://snapframework.com" 301)
HTTP/1.1 307 Temporary Redirect
content-length: 0
location: http://snapframework.com
server: Snap/test
date: Thu, 07 Aug 2014 08:55:51 GMT
Content-Length: 0
Response I/O
:: (OutputStream Builder -> IO (OutputStream Builder)) | new response body |
-> Response | response to modify |
-> Response |
Sets an HTTP response body to the given stream procedure.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified System.IO.Streams as Streams ghci> import qualified Data.ByteString.Builder as Builder ghci> :{ ghci| let r =setResponseBody
ghci| (out -> do ghci| Streams.write (Just $ Builder.byteString
"Hello, world!") out ghci| return out) ghci|emptyResponse
ghci| :} ghci> r HTTP/1.1 200 OK Hello, world!
modifyResponseBody :: ((OutputStream Builder -> IO (OutputStream Builder)) -> OutputStream Builder -> IO (OutputStream Builder)) -> Response -> Response Source #
Modifies a response body.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified System.IO.Streams as Streams ghci> import qualified Data.ByteString.Builder as Builder ghci> :{ ghci| let r =setResponseBody
ghci| (out -> do ghci| Streams.write (Just $ Builder.byteString
"Hello, world!") out ghci| return out) ghci|emptyResponse
ghci| :} ghci> r HTTP/1.1 200 OK Hello, world! ghci> :{ ghci| let r' =modifyResponseBody
ghci| (f out -> do ghci| out' <- f out ghci| Streams.write (Just $ Builder.byteString
"\nBye, world!") out' ghci| return out') r ghci| :} ghci> r' HTTP/1.1 200 OK Hello, world! Bye, world!
:: MonadSnap m | |
=> (OutputStream Builder -> IO (OutputStream Builder)) | output to add |
-> m () |
Run the given stream procedure, adding its output to the Response
stored
in the Snap
monad state.
Example:
ghci> :set -XOverloadedStrings
ghci> import qualified Data.Map as M
ghci> import qualified Snap.Test as T
ghci> import qualified Data.ByteString.Builder as B
ghci> import qualified System.IO.Streams as Streams
ghci> let r = T.get "/foo/bar" M.empty
ghci> :{
ghci| let f str = do {
ghci| Streams.write (Just $ B.byteString "Hello, streams world") str;
ghci| return str }
ghci| :}
ghci> T.runHandler r (addToOutput
f)
HTTP/1.1 200 OK
server: Snap/test
date: Wed, 06 Aug 2014 17:55:47 GMT
Hello, streams world
writeBuilder :: MonadSnap m => Builder -> m () Source #
Adds the given Builder
to the body of the Response
stored in the
| Snap
monad state.
Example:
ghci> :set -XOverloadedStrings
ghci> import qualified Data.Map as M
ghci> import qualified Snap.Test as T
ghci> import qualified Data.ByteString.Builder as B
ghci> let r = T.get "/foo/bar" M.empty
ghci> T.runHandler r (writeBuilder
$ B.byteString "Hello, world")
HTTP/1.1 200 OK
server: Snap/test
date: Wed, 06 Aug 2014 17:33:33 GMT
Hello, world
writeBS :: MonadSnap m => ByteString -> m () Source #
Adds the given strict ByteString
to the body of the Response
stored
in the Snap
monad state.
Warning: This function is intentionally non-strict. If any pure
exceptions are raised by the expression creating the ByteString
,
the exception won't actually be raised within the Snap handler.
Example:
ghci> :set -XOverloadedStrings
ghci> import qualified Data.Map as M
ghci> import qualified Snap.Test as T
ghci> let r = T.get "/foo/bar" M.empty
ghci> T.runHandler r (writeBS
"Hello, bytestring world")
HTTP/1.1 200 OK
server: Snap/test
date: Wed, 06 Aug 2014 17:34:27 GMT
Hello, bytestring world
writeLazyText :: MonadSnap m => Text -> m () Source #
Adds the given lazy Text
to the body of the Response
stored in the
Snap
monad state.
Warning: This function is intentionally non-strict. If any pure
exceptions are raised by the expression creating the ByteString
,
the exception won't actually be raised within the Snap handler.
Example:
ghci> :set -XOverloadedStrings
ghci> import qualified Data.Map as M
ghci> import qualified Snap.Test as T
ghci> let r = T.get "/foo/bar" M.empty
ghci> T.runHandler r (writeLazyText
"Hello, lazy text world")
HTTP/1.1 200 OK
server: Snap/test
date: Wed, 06 Aug 2014 17:37:41 GMT
Hello, lazy text world
writeText :: MonadSnap m => Text -> m () Source #
Adds the given strict Text
to the body of the Response
stored in
the Snap
monad state.
Warning: This function is intentionally non-strict. If any pure
exceptions are raised by the expression creating the ByteString
,
the exception won't actually be raised within the Snap handler.
Example:
ghci> :set -XOverloadedStrings
ghci> import qualified Data.Map as M
ghci> import qualified Snap.Test as T
ghci> let r = T.get "/foo/bar" M.empty
ghci> T.runHandler r (writeText
"Hello, text world")
HTTP/1.1 200 OK
server: Snap/test
date: Wed, 06 Aug 2014 17:36:38 GMT
Hello, text world
writeLBS :: MonadSnap m => ByteString -> m () Source #
Adds the given lazy ByteString
to the body of the Response
stored
in the Snap
monad state.
Warning: This function is intentionally non-strict. If any pure
exceptions are raised by the expression creating the ByteString
,
the exception won't actually be raised within the Snap handler.
Example:
ghci> :set -XOverloadedStrings
ghci> import qualified Data.Map as M
ghci> import qualified Snap.Test as T
ghci> let r = T.get "/foo/bar" M.empty
ghci> T.runHandler r (writeLBS
"Hello, lazy bytestring world")
HTTP/1.1 200 OK
server: Snap/test
date: Wed, 06 Aug 2014 17:35:15 GMT
Hello, lazy bytestring world
sendFile :: MonadSnap m => FilePath -> m () Source #
Sets the output to be the contents of the specified file.
Calling sendFile
will overwrite any output queued to be sent in the
Response
. If the response body is not modified after the call to
sendFile
, Snap will use the efficient sendfile()
system call on
platforms that support it.
If the response body is modified (using modifyResponseBody
), the file
will be read using mmap()
.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci>writeFile
"/tmp/snap-file" "Hello, sendFile world" ghci> let r = T.get "/foo/bar" M.empty ghci> T.runHandler r (sendFile
"/tmp/snap-file") HTTP/1.1 200 OK content-length: 21 server: Snap/test date: Wed, 06 Aug 2014 17:45:10 GMT Content-Length: 21 Hello, sendFile world
sendFilePartial :: MonadSnap m => FilePath -> (Word64, Word64) -> m () Source #
Sets the output to be the contents of the specified file, within the given (start,end) range.
Calling sendFilePartial
will overwrite any output queued to be sent in
the Response
. If the response body is not modified after the call to
sendFilePartial
, Snap will use the efficient sendfile()
system call on
platforms that support it.
If the response body is modified (using modifyResponseBody
), the file
will be read using mmap()
.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import qualified Snap.Test as T ghci>writeFile
"/tmp/snap-file" "Hello, sendFilePartial world" ghci> let r = T.get "/foo/bar" M.empty ghci> T.runHandler r (sendFilePartial
"/tmp/snap-file" (7, 28)) HTTP/1.1 200 OK content-length: 21 server: Snap/test date: Wed, 06 Aug 2014 17:47:20 GMT Content-Length: 21 sendFilePartial world
Timeouts
setTimeout :: MonadSnap m => Int -> m () Source #
Causes the handler thread to be killed n
seconds from now.
extendTimeout :: MonadSnap m => Int -> m () Source #
Causes the handler thread to be killed at least n
seconds from now.
modifyTimeout :: MonadSnap m => (Int -> Int) -> m () Source #
Modifies the amount of time remaining before the request times out.
getTimeoutModifier :: MonadSnap m => m ((Int -> Int) -> IO ()) Source #
Returns an IO
action which you can use to modify the timeout value.
HTTP utilities
formatHttpTime :: CTime -> IO ByteString Source #
Convert a CTime
into an HTTP timestamp.
Example:
ghci>formatHttpTime
.fromIntegral
$ 10 "Thu, 01 Jan 1970 00:00:10 GMT"
parseHttpTime :: ByteString -> IO CTime Source #
Converts an HTTP timestamp into a CTime
.
Example:
ghci> :set -XOverloadedStrings
ghci> parseHttpTime
"Thu, 01 Jan 1970 00:00:10 GMT"
10
parseUrlEncoded :: ByteString -> Map ByteString [ByteString] Source #
buildUrlEncoded :: Map ByteString [ByteString] -> Builder Source #
Like printUrlEncoded
, but produces a Builder
instead of a
ByteString
. Useful for constructing a large string efficiently in
a single step.
Example:
ghci> import Data.Map ghci> import Data.Monoid ghci> import Data.ByteString.Builder ghci> let bldr =buildUrlEncoded
(fromList
[(Name, ["John Doe"]), (Age, ["23"])]) ghci>toLazyByteString
$byteString
"http://example.com/script?" <> bldr "http://example.com/script?Age=23&Name=John+Doe"
printUrlEncoded :: Map ByteString [ByteString] -> ByteString Source #
Given a collection of key-value pairs with possibly duplicate
keys (represented as a Map
), construct a string in
application/x-www-form-urlencoded
format.
Example:
ghci>printUrlEncoded
(fromList
[(Name, ["John Doe"]), (Age, ["23"])]) "Age=23&Name=John+Doe"
urlEncode :: ByteString -> ByteString Source #
URL-escape a string (see http://tools.ietf.org/html/rfc2396.html#section-2.4)
Example:
ghci> urlEncode
"1 attoparsec ~= 3 * 10^-2 meters"
"1+attoparsec+%7e%3d+3+*+10%5e-2+meters"
urlEncodeBuilder :: ByteString -> Builder Source #
URL-escape a string (see
http://tools.ietf.org/html/rfc2396.html#section-2.4) into a Builder
.
Example:
ghci> import Data.ByteString.Builder ghci>toLazyByteString
.urlEncodeBuilder
$ "1 attoparsec ~= 3 * 10^-2 meters" "1+attoparsec+%7e%3d+3+*+10%5e-2+meters"
urlDecode :: ByteString -> Maybe ByteString Source #
Decode an URL-escaped string (see http://tools.ietf.org/html/rfc2396.html#section-2.4)
Example:
ghci> urlDecode
"1+attoparsec+%7e%3d+3+*+10%5e-2+meters"
Just "1 attoparsec ~= 3 * 10^-2 meters"