snap-core-1.0.3.1: Snap: A Haskell Web Framework (core interfaces and types)

Safe HaskellNone
LanguageHaskell2010

Snap.Internal.Http.Types

Description

An internal Snap module containing HTTP types.

N.B. this is an internal interface, please don't write user code that depends on it. Most of these declarations (except for the unsafe/encapsulation-breaking ones) are re-exported from Snap.Core.

Synopsis

Documentation

class HasHeaders a where Source #

A typeclass for datatypes which contain HTTP headers.

Minimal complete definition

updateHeaders, headers

Methods

updateHeaders :: (Headers -> Headers) -> a -> a Source #

Modify the datatype's headers.

headers :: a -> Headers Source #

Retrieve the headers from a datatype that has 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 = []}

normalizeMethod :: Method -> Method Source #

Equate the special case constructors with their corresponding Method name variant.

type HttpVersion = (Int, Int) Source #

Represents a (major, minor) version of the HTTP protocol.

data Cookie Source #

A datatype representing an HTTP cookie.

Constructors

Cookie 

Fields

Instances

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&param=bar2"), looking up "param" in the mapping will give you ["bar1", "bar2"].

data Request Source #

Contains all of the information about an incoming HTTP request.

Constructors

Request 

Fields

  • rqHostName :: ByteString

    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 :: ByteString

    The remote IP address.

    Example:

    ghci> :set -XOverloadedStrings
    ghci> import qualified Snap.Test as T
    ghci> import qualified Data.Map as M
    ghci> rqClientAddr `fmap` T.buildRequest (T.get "/foo/bar" M.empty)
    "127.0.0.1"
    
  • rqClientPort :: !Int

    The remote TCP port number.

    Example:

    ghci> :set -XOverloadedStrings
    ghci> import qualified Snap.Test as T
    ghci> import qualified Data.Map as M
    ghci> rqClientPort `fmap` T.buildRequest (T.get "/foo/bar" M.empty)
    "60000"
    
  • rqServerAddr :: ByteString

    The local IP address for this request.

    Example:

    ghci> :set -XOverloadedStrings
    ghci> import qualified Snap.Test as T
    ghci> import qualified Data.Map as M
    ghci> rqServerAddr `fmap` T.buildRequest (T.get "/foo/bar" M.empty)
    "127.0.0.1"
    
  • rqServerPort :: !Int

    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 :: ByteString

    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 :: !Bool

    Returns True if this is an HTTPS session.

    Example:

    ghci> :set -XOverloadedStrings
    ghci> import qualified Snap.Test as T
    ghci> import qualified Data.Map as M
    ghci> rqIsSecure `fmap` T.buildRequest (T.get "/foo/bar" M.empty)
    False
    
  • rqHeaders :: Headers

    Contains all HTTP Headers associated with this request.

    Example:

    ghci> :set -XOverloadedStrings
    ghci> import qualified Snap.Test as T
    ghci> import qualified Data.Map as M
    ghci> rqHeaders `fmap` T.buildRequest (T.get "/foo/bar" M.empty)
    H {unH = [("host","localhost")]}
    
  • rqBody :: InputStream ByteString

    Actual body of the request.

  • rqContentLength :: !(Maybe Word64)

    Returns the Content-Length of the HTTP request body.

    Example:

    ghci> :set -XOverloadedStrings
    ghci> import qualified Snap.Test as T
    ghci> import qualified Data.Map as M
    ghci> rqContentLength `fmap` T.buildRequest (T.get "/foo/bar" M.empty)
    Nothing
    
  • rqMethod :: !Method

    Returns the HTTP request method.

    Example:

    ghci> :set -XOverloadedStrings
    ghci> import qualified Snap.Test as T
    ghci> import qualified Data.Map as M
    ghci> rqMethod `fmap` T.buildRequest (T.get "/foo/bar" M.empty)
    GET
    
  • rqVersion :: !HttpVersion

    Returns the HTTP version used by the client.

    Example:

    ghci> :set -XOverloadedStrings
    ghci> import qualified Snap.Test as T
    ghci> import qualified Data.Map as M
    ghci> rqVersion `fmap` T.buildRequest (T.get "/foo/bar" M.empty)
    (1,1)
    
  • rqCookies :: [Cookie]

    Returns a list of the cookies that came in from the HTTP request headers.

    Example:

    ghci> :set -XOverloadedStrings
    ghci> import qualified Snap.Test as T
    ghci> import qualified Data.Map as M
    ghci> rqCookies `fmap` T.buildRequest (T.get "/foo/bar" M.empty)
    []
    
  • rqPathInfo :: ByteString

    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 :: ByteString

    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 :: ByteString

    Returns the URI requested by the client.

    Example:

    ghci> :set -XOverloadedStrings
    ghci> import qualified Snap.Test as T
    ghci> import qualified Data.Map as M
    ghci> rqURI `fmap` T.buildRequest (T.get "/foo/bar" M.empty)
    "foo/bar"
    
  • rqQueryString :: ByteString

    Returns the HTTP query string for this Request.

    Example:

    ghci> :set -XOverloadedStrings
    ghci> import qualified Snap.Test as T
    ghci> import qualified Data.Map as M
    ghci> rq <- T.buildRequest (T.get "/foo/bar" (M.fromList [("name", ["value"])]))
    ghci> rqQueryString rq
    "name=value"
    
  • rqParams :: Params

    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 :: Params

    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 :: Params

    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"])]
    

data ResponseBody Source #

Constructors

Stream StreamProc

output body is a function that writes to a Builder stream

SendFile FilePath (Maybe (Word64, Word64))

output body is sendfile(), optional second argument is a byte range to send

data Response Source #

Represents an HTTP response.

Constructors

Response 

Fields

rqParam Source #

Arguments

:: 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"]

rqPostParam Source #

Arguments

:: 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"]

rqQueryParam Source #

Arguments

:: 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"]

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 []

rqSetParam Source #

Arguments

:: 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"])]

emptyResponse :: Response Source #

An empty Response.

Example:

ghci> emptyResponse
HTTP/1.1 200 OK


setResponseBody Source #

Arguments

:: (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!

setResponseStatus Source #

Arguments

:: 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


setResponseCode Source #

Arguments

:: Int

HTTP response integer code

-> Response

Response to be modified

-> Response 

Sets the HTTP response code.

Example:

ghci> setResponseCode 404 emptyResponse
HTTP/1.1 404 Not Found


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!

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


cookieToBS :: Cookie -> ByteString Source #

Convert Cookie into ByteString for output.

TODO: Remove duplication. This function is copied from snap-server/Snap.Internal.Http.Server.Session.

renderCookies :: Response -> Headers -> Headers Source #

Render cookies from a given Response to Headers.

TODO: Remove duplication. This function is copied from snap-server/Snap.Internal.Http.Server.Session.

addResponseCookie Source #

Arguments

:: Cookie

cookie value

-> Response

response to modify

-> Response 

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 cookie emptyResponse
Just (Cookie {cookieName = "name", cookieValue = "value", ...})

getResponseCookie Source #

Arguments

:: 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

getResponseCookies Source #

Arguments

:: Response

response to query

-> [Cookie] 

Returns a list of Cookies present in Response

Example:

ghci> getResponseCookies emptyResponse
[]

deleteResponseCookie Source #

Arguments

:: 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 cookie emptyResponse
ghci> getResponseCookie "name" rsp
Just (Cookie {cookieName = "name", cookieValue = "value", ...})
ghci> getResponseCookie "name" $ deleteResponseCookie "name" rsp
Nothing

modifyResponseCookie Source #

Arguments

:: 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 cookie emptyResponse
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", ...})

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 400 emptyResponse
HTTP/1.1 200 OK


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"

formatLogTime :: CTime -> IO ByteString Source #

Convert a CTime into common log entry format.

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

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.