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

Safe HaskellNone
LanguageHaskell2010

Happstack.Server.Internal.Types

Synopsis

Documentation

data Request Source #

an HTTP request

Constructors

Request 

Fields

Instances
Show Request Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

showsPrec :: Int -> Request -> ShowS

show :: Request -> String

showList :: [Request] -> ShowS

data Response Source #

an HTTP Response

Constructors

Response 

Fields

SendFile 

Fields

Instances
Show Response Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

showsPrec :: Int -> Response -> ShowS

show :: Response -> String

showList :: [Response] -> ShowS

Error Response Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

noMsg :: Response

strMsg :: String -> Response

ToMessage Response Source # 
Instance details

Defined in Happstack.Server.Response

Methods

toContentType :: Response -> ByteString Source #

toMessage :: Response -> ByteString Source #

toResponse :: Response -> Response Source #

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

Instances
Read RqBody Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

readsPrec :: Int -> ReadS RqBody

readList :: ReadS [RqBody]

readPrec :: ReadPrec RqBody

readListPrec :: ReadPrec [RqBody]

Show RqBody Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

showsPrec :: Int -> RqBody -> ShowS

show :: RqBody -> String

showList :: [RqBody] -> ShowS

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.

Constructors

Input 

Fields

Instances
Read Input Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

readsPrec :: Int -> ReadS Input

readList :: ReadS [Input]

readPrec :: ReadPrec Input

readListPrec :: ReadPrec [Input]

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

  • hName :: ByteString

    header name

  • hValue :: [ByteString]

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

Instances
Read HeaderPair Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

readsPrec :: Int -> ReadS HeaderPair

readList :: ReadS [HeaderPair]

readPrec :: ReadPrec HeaderPair

readListPrec :: ReadPrec [HeaderPair]

Show HeaderPair Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

showsPrec :: Int -> HeaderPair -> ShowS

show :: HeaderPair -> String

showList :: [HeaderPair] -> ShowS

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

  • 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 (LogAccess t)

    function to log access requests (see also: logMAccess)

  • timeout :: Int

    number of seconds to wait before killing an inactive thread

  • threadGroup :: Maybe ThreadGroup

    ThreadGroup for registering spawned threads for handling requests

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

Instances
Read RsFlags Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

readsPrec :: Int -> ReadS RsFlags

readList :: ReadS [RsFlags]

readPrec :: ReadPrec RsFlags

readListPrec :: ReadPrec [RsFlags]

Show RsFlags Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

showsPrec :: Int -> RsFlags -> ShowS

show :: RsFlags -> String

showList :: [RsFlags] -> ShowS

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

HTTP version

Constructors

HttpVersion Int Int 
Instances
Eq HttpVersion Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

(==) :: HttpVersion -> HttpVersion -> Bool

(/=) :: HttpVersion -> HttpVersion -> Bool

Read HttpVersion Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

readsPrec :: Int -> ReadS HttpVersion

readList :: ReadS [HttpVersion]

readPrec :: ReadPrec HttpVersion

readListPrec :: ReadPrec [HttpVersion]

Show HttpVersion Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

showsPrec :: Int -> HttpVersion -> ShowS

show :: HttpVersion -> String

showList :: [HttpVersion] -> ShowS

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.

Instances
Enum Length Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Eq Length Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

(==) :: Length -> Length -> Bool

(/=) :: Length -> Length -> Bool

Ord Length Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

compare :: Length -> Length -> Ordering

(<) :: Length -> Length -> Bool

(<=) :: Length -> Length -> Bool

(>) :: Length -> Length -> Bool

(>=) :: Length -> Length -> Bool

max :: Length -> Length -> Length

min :: Length -> Length -> Length

Read Length Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

readsPrec :: Int -> ReadS Length

readList :: ReadS [Length]

readPrec :: ReadPrec Length

readListPrec :: ReadPrec [Length]

Show Length Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

showsPrec :: Int -> Length -> ShowS

show :: Length -> String

showList :: [Length] -> ShowS

data Method Source #

HTTP request method

Constructors

GET 
HEAD 
POST 
PUT 
DELETE 
TRACE 
OPTIONS 
CONNECT 
PATCH 
EXTENSION ByteString 
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

Methods

compare :: Method -> Method -> Ordering

(<) :: Method -> Method -> Bool

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

(>) :: Method -> Method -> Bool

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

max :: Method -> Method -> Method

min :: Method -> Method -> Method

Read Method Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

readsPrec :: Int -> ReadS Method

readList :: ReadS [Method]

readPrec :: ReadPrec Method

readListPrec :: ReadPrec [Method]

Show Method Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

showsPrec :: Int -> Method -> ShowS

show :: Method -> String

showList :: [Method] -> ShowS

MatchMethod Method Source # 
Instance details

Defined in Happstack.Server.Routing

Methods

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

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 #

canHaveBody :: Method -> Bool Source #

Does the method support a message body?

For extension methods, we assume yes.

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

Instances
Eq ContentType Source # 
Instance details

Defined in Happstack.Server.Internal.RFC822Headers

Methods

(==) :: ContentType -> ContentType -> Bool

(/=) :: ContentType -> ContentType -> Bool

Ord ContentType Source # 
Instance details

Defined in Happstack.Server.Internal.RFC822Headers

Read ContentType Source # 
Instance details

Defined in Happstack.Server.Internal.RFC822Headers

Methods

readsPrec :: Int -> ReadS ContentType

readList :: ReadS [ContentType]

readPrec :: ReadPrec ContentType

readListPrec :: ReadPrec [ContentType]

Show ContentType Source # 
Instance details

Defined in Happstack.Server.Internal.RFC822Headers

Methods

showsPrec :: Int -> ContentType -> ShowS

show :: ContentType -> String

showList :: [ContentType] -> ShowS

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

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

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

readM :: (Monad m, Read t) => String -> m t Source #

Read in any monad.

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

Methods

fromReqURI :: String -> Maybe Bool Source #

FromReqURI Char Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Char Source #

FromReqURI Double Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Double Source #

FromReqURI Float Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Float Source #

FromReqURI Int Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Int Source #

FromReqURI Int8 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Int8 Source #

FromReqURI Int16 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Int16 Source #

FromReqURI Int32 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Int32 Source #

FromReqURI Int64 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Int64 Source #

FromReqURI Integer Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Integer Source #

FromReqURI Word Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Word Source #

FromReqURI Word8 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Word8 Source #

FromReqURI Word16 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Word16 Source #

FromReqURI Word32 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Word32 Source #

FromReqURI Word64 Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Word64 Source #

FromReqURI String Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe String Source #

FromReqURI Text Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Text Source #

FromReqURI Text Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

fromReqURI :: String -> Maybe Text Source #

showRsValidator :: Maybe (Response -> IO Response) -> String Source #

data EscapeHTTP Source #

Escape from the HTTP world and get direct access to the underlying TimeoutIO functions

Constructors

EscapeHTTP (TimeoutIO -> IO ()) 
Instances
Show EscapeHTTP Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

showsPrec :: Int -> EscapeHTTP -> ShowS

show :: EscapeHTTP -> String

showList :: [EscapeHTTP] -> ShowS

Exception EscapeHTTP Source # 
Instance details

Defined in Happstack.Server.Internal.Types

Methods

toException :: EscapeHTTP -> SomeException

fromException :: SomeException -> Maybe EscapeHTTP

displayException :: EscapeHTTP -> String