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

Happstack.Server.Internal.Types

Synopsis

Documentation

data Response Source

an HTTP Response

Constructors

Response 
SendFile 

Fields

rsCode :: Int
 
rsHeaders :: Headers
 
rsFlags :: RsFlags
 
rsValidator :: Maybe (Response -> IO Response)
 
sfFilePath :: FilePath

file handle to send from

sfOffset :: Integer

offset to start at

sfCount :: Integer

number of bytes to send

newtype RqBody Source

The body of an HTTP Request

Constructors

Body 

Fields

unBody :: ByteString
 

data Input Source

a value extract from the QUERY_STRING or Request body

If the input value was a file, then it will be saved to a temporary file on disk and inputValue will contain Left pathToTempFile.

data HeaderPair Source

an HTTP header

Constructors

HeaderPair 

Fields

hName :: ByteString

header name

hValue :: [ByteString]

header value (or values if multiple occurances of the header are present)

Instances

takeRequestBody :: MonadIO m => Request -> m (Maybe RqBody)Source

get the request body from the Request and replace it with Nothing

IMPORTANT: You can really only call this function once. Subsequent calls will return Nothing.

readInputsBody :: Request -> IO (Maybe [(String, Input)])Source

read the request body inputs

This will only work if the body inputs have already been decoded. Otherwise it will return Nothing.

rqURL :: Request -> StringSource

Converts a Request into a String representing the corresponding URL

mkHeaders :: [(String, String)] -> HeadersSource

Takes a list of (key,val) pairs and converts it into Headers. The keys will be converted to lowercase

getHeader :: HasHeaders r => String -> r -> Maybe ByteStringSource

Lookup header value. Key is case-insensitive.

getHeaderBS :: HasHeaders r => ByteString -> r -> Maybe ByteStringSource

Lookup header value. Key is a case-insensitive bytestring.

getHeaderUnsafe :: HasHeaders r => ByteString -> r -> Maybe ByteStringSource

Lookup header value with a case-sensitive key. The key must be lowercase.

hasHeader :: HasHeaders r => String -> r -> BoolSource

Returns True if the associated key is found in the Headers. The lookup is case insensitive.

hasHeaderBS :: HasHeaders r => ByteString -> r -> BoolSource

Acts as hasHeader with ByteStrings

hasHeaderUnsafe :: HasHeaders r => ByteString -> r -> BoolSource

Acts as hasHeaderBS but the key is case sensitive. It should be in lowercase.

setHeader :: HasHeaders r => String -> String -> r -> rSource

Associates the key/value pair in the headers. Forces the key to be lowercase.

setHeaderBS :: HasHeaders r => ByteString -> ByteString -> r -> rSource

Acts as setHeader but with ByteStrings.

setHeaderUnsafe :: HasHeaders r => ByteString -> HeaderPair -> r -> rSource

Sets the key to the HeaderPair. This is the only way to associate a key with multiple values via the setHeader* functions. Does not force the key to be in lowercase or guarantee that the given key and the key in the HeaderPair will match.

addHeader :: HasHeaders r => String -> String -> r -> rSource

Add a key/value pair to the header. If the key already has a value associated with it, then the value will be appended. Forces the key to be lowercase.

addHeaderBS :: HasHeaders r => ByteString -> ByteString -> r -> rSource

Acts as addHeader except for ByteStrings

addHeaderUnsafe :: HasHeaders r => ByteString -> HeaderPair -> r -> rSource

Add a key/value pair to the header using the underlying HeaderPair data type. Does not force the key to be in lowercase or guarantee that the given key and the key in the HeaderPair will match.

setRsCode :: Monad m => Int -> Response -> m ResponseSource

Sets the Response status code to the provided Int and lifts the computation into a Monad.

data Conf Source

HTTP configuration

Constructors

Conf 

Fields

port :: Int

Port for the server to listen on.

validator :: Maybe (Response -> IO Response)

a function to validate the output on-the-fly

logAccess :: forall t. FormatTime t => Maybe (String -> String -> t -> String -> Int -> Integer -> String -> String -> IO ())

function to log access requests (see also: logMAccess)

timeout :: Int

number of seconds to wait before killing an inactive thread

nullConf :: ConfSource

Default configuration contains no validator and the port is set to 8000

result :: Int -> String -> ResponseSource

Creates a Response with the given Int as the status code and the provided String as the body of the Response

resultBS :: Int -> ByteString -> ResponseSource

Acts as result but works with ByteStrings directly.

By default, Transfer-Encoding: chunked will be used

redirect :: ToSURI s => Int -> s -> Response -> ResponseSource

Sets the Response's status code to the given Int and redirects to the given URI

isHTTP1_0 :: Request -> BoolSource

True if Request is HTTP version 1.0

isHTTP1_1 :: Request -> BoolSource

True if Request is HTTP version 1.1

data RsFlags Source

Result flags

Constructors

RsFlags 

Fields

rsfLength :: Length
 

nullRsFlags :: RsFlagsSource

Default RsFlags: automatically use Transfer-Encoding: Chunked.

contentLength :: Response -> ResponseSource

Automatically add a Content-Length header. Do not use Transfer-Encoding: Chunked

chunked :: Response -> ResponseSource

Do not automatically add a Content-Length header. Do automatically use Transfer-Encoding: Chunked

noContentLength :: Response -> ResponseSource

Do not automatically add a Content-Length field to the Response

data HttpVersion Source

HTTP version

Constructors

HttpVersion Int Int 

data Length Source

A flag value set in the Response which controls how the Content-Length header is set, and whether *chunked* output encoding is used.

see also: nullRsFlags, notContentLength, and chunked

Constructors

ContentLength

automatically add a Content-Length header to the Response

TransferEncodingChunked

do not add a Content-Length header. Do use chunked output encoding

NoContentLength

do not set Content-Length or chunked output encoding.

data Method Source

log access requests using hslogger and apache-style log formatting

see also: Conf

HTTP request method

Constructors

GET 
HEAD 
POST 
PUT 
DELETE 
TRACE 
OPTIONS 
CONNECT 

type HeadersSource

Arguments

 = Map ByteString HeaderPair

lowercased name -> (realname, value)

Combined headers.

a Map of HTTP headers

the Map key is the header converted to lowercase

continueHTTP :: Request -> Response -> BoolSource

Should the connection be used for further messages after this. | isHTTP1_0 && hasKeepAlive || isHTTP1_1 && hasNotConnectionClose

type HostSource

Arguments

 = (String, Int)

(hostname, port)

hostname & port

data ContentType Source

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

Constructors

ContentType 

Fields

ctType :: String

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

ctSubtype :: String

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

ctParameters :: [(String, String)]

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