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

Safe HaskellNone
LanguageHaskell2010

Happstack.Server.Types

Synopsis

Documentation

data Request Source #

an HTTP request

Constructors

Request 

Fields

Instances
Show Request Source # 
Instance details

Defined in Happstack.Server.Internal.Types

data Response Source #

an HTTP Response

Constructors

Response 
SendFile 

Fields

Instances
Show Response Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Error Response Source # 
Instance details

Defined in Happstack.Server.Internal.Types

ToMessage Response Source # 
Instance details

Defined in Happstack.Server.Response

Monad m => WebMonad Response (WebT m) Source # 
Instance details

Defined in Happstack.Server.Internal.Monads

Methods

finishWith :: Response -> WebT m b Source #

Monad m => WebMonad Response (ServerPartT m) Source # 
Instance details

Defined in Happstack.Server.Internal.Monads

Monad m => FilterMonad Response (WebT m) Source # 
Instance details

Defined in Happstack.Server.Internal.Monads

Monad m => FilterMonad Response (ServerPartT m) Source # 
Instance details

Defined in Happstack.Server.Internal.Monads

newtype RqBody Source #

The body of an HTTP Request

Constructors

Body 

Fields

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.

Instances
Read Input Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Show Input Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

showsPrec :: Int -> Input -> ShowS #

show :: Input -> String #

showList :: [Input] -> ShowS #

MonadReader RqEnv RqData Source # 
Instance details

Defined in Happstack.Server.RqData

Methods

ask :: RqData RqEnv #

local :: (RqEnv -> RqEnv) -> RqData a -> RqData a #

reader :: (RqEnv -> a) -> RqData a #

data HeaderPair Source #

an HTTP header

Constructors

HeaderPair 

Fields

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 -> String Source #

Converts a Request into a String representing the corresponding URL

mkHeaders :: [(String, String)] -> Headers Source #

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 ByteString Source #

Lookup header value. Key is case-insensitive.

getHeaderBS :: HasHeaders r => ByteString -> r -> Maybe ByteString Source #

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

getHeaderUnsafe :: HasHeaders r => ByteString -> r -> Maybe ByteString Source #

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

hasHeader :: HasHeaders r => String -> r -> Bool Source #

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

hasHeaderBS :: HasHeaders r => ByteString -> r -> Bool Source #

Acts as hasHeader with ByteStrings

hasHeaderUnsafe :: HasHeaders r => ByteString -> r -> Bool Source #

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

setHeader :: HasHeaders r => String -> String -> r -> r Source #

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

setHeaderBS :: HasHeaders r => ByteString -> ByteString -> r -> r Source #

Acts as setHeader but with ByteStrings.

setHeaderUnsafe :: HasHeaders r => ByteString -> HeaderPair -> r -> r Source #

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 -> r Source #

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 -> r Source #

Acts as addHeader except for ByteStrings

addHeaderUnsafe :: HasHeaders r => ByteString -> HeaderPair -> r -> r Source #

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 Response Source #

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

type LogAccess time = String -> String -> time -> String -> Int -> Integer -> String -> String -> IO () Source #

function to log access requests (see also: logMAccess) type LogAccess time = ( String -- ^ host -> String -- ^ user -> time -- ^ time -> String -- ^ requestLine -> Int -- ^ responseCode -> Integer -- ^ size -> String -- ^ referer -> String -- ^ userAgent -> IO ())

logMAccess :: forall t. FormatTime t => LogAccess t Source #

log access requests using hslogger and apache-style log formatting

see also: Conf

data Conf Source #

HTTP configuration

Constructors

Conf 

Fields

nullConf :: Conf Source #

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

result :: Int -> String -> Response Source #

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

resultBS :: Int -> ByteString -> Response Source #

Acts as result but works with ByteStrings directly.

By default, Transfer-Encoding: chunked will be used

redirect :: ToSURI s => Int -> s -> Response -> Response Source #

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

isHTTP1_0 :: Request -> Bool Source #

True if Request is HTTP version 1.0

isHTTP1_1 :: Request -> Bool Source #

True if Request is HTTP version 1.1

data RsFlags Source #

Result flags

Constructors

RsFlags 

Fields

nullRsFlags :: RsFlags Source #

Default RsFlags: automatically use Transfer-Encoding: Chunked.

contentLength :: Response -> Response Source #

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

chunked :: Response -> Response Source #

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

noContentLength :: Response -> Response Source #

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

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 #

HTTP request method

Instances
Eq Method Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

(==) :: Method -> Method -> Bool #

(/=) :: Method -> Method -> Bool #

Data Method Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Method -> c Method #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Method #

toConstr :: Method -> Constr #

dataTypeOf :: Method -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Method) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Method) #

gmapT :: (forall b. Data b => b -> b) -> Method -> Method #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Method -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Method -> r #

gmapQ :: (forall d. Data d => d -> u) -> Method -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Method -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Method -> m Method #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Method -> m Method #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Method -> m Method #

Ord Method Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Read Method Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Show Method Source # 
Instance details

Defined in Happstack.Server.Internal.Types

MatchMethod Method Source # 
Instance details

Defined in Happstack.Server.Routing

MatchMethod [Method] Source # 
Instance details

Defined in Happstack.Server.Routing

Methods

matchMethod :: [Method] -> Method -> Bool Source #

MatchMethod (Method -> Bool) Source # 
Instance details

Defined in Happstack.Server.Routing

Methods

matchMethod :: (Method -> Bool) -> Method -> Bool Source #

type Headers Source #

Arguments

 = Map ByteString HeaderPair

lowercased name -> (realname, value)

a Map of HTTP headers

the Map key is the header converted to lowercase

continueHTTP :: Request -> Response -> Bool Source #

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

In addition to this rule All 1xx (informational), 204 (no content), and 304 (not modified) responses MUST NOT include a message-body and therefore are eligible for connection keep-alive.

type Host Source #

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

readDec' :: (Num a, Eq a) => String -> a Source #

fromReadS :: [(a, String)] -> Maybe a Source #

convert a 'ReadS a' result to 'Maybe a'

class FromReqURI a where Source #

This class is used by path to parse a path component into a value.

The instances for number types (Int, Float, etc) use readM to parse the path component.

The instance for String, on the other hand, returns the unmodified path component.

See the following section of the Happstack Crash Course for detailed instructions using and extending FromReqURI:

http://www.happstack.com/docs/crashcourse/RouteFilters.html#FromReqURI

Methods

fromReqURI :: String -> Maybe a Source #

Instances
FromReqURI Bool Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Char Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Double Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Float Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Int Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Int8 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Int16 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Int32 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Int64 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Integer Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Word Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Word8 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Word16 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Word32 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Word64 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI String Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Text Source # 
Instance details

Defined in Happstack.Server.Internal.Types

FromReqURI Text Source # 
Instance details

Defined in Happstack.Server.Internal.Types