happstack-server-0.3.1: Web related tools and services.Source codeContentsIndex
Happstack.Server.HTTP.Types
Synopsis
data Request = Request {
rqMethod :: Method
rqPaths :: [String]
rqUri :: String
rqQuery :: String
rqInputs :: [(String, Input)]
rqCookies :: [(String, Cookie)]
rqVersion :: Version
rqHeaders :: Headers
rqBody :: RqBody
rqPeer :: Host
}
data Response = Response {
rsCode :: Int
rsHeaders :: Headers
rsFlags :: RsFlags
rsBody :: ByteString
rsValidator :: Maybe (Response -> IO Response)
}
newtype RqBody = Body ByteString
data Input = Input {
inputValue :: ByteString
inputFilename :: Maybe String
inputContentType :: ContentType
}
data HeaderPair = HeaderPair {
hName :: ByteString
hValue :: [ByteString]
}
rqURL :: Request -> String
mkHeaders :: [(String, String)] -> Headers
getHeader :: HasHeaders r => String -> r -> Maybe ByteString
getHeaderBS :: HasHeaders r => ByteString -> r -> Maybe ByteString
getHeaderUnsafe :: HasHeaders r => ByteString -> r -> Maybe ByteString
hasHeader :: HasHeaders r => String -> r -> Bool
hasHeaderBS :: HasHeaders r => ByteString -> r -> Bool
hasHeaderUnsafe :: HasHeaders r => ByteString -> r -> Bool
setHeader :: HasHeaders r => String -> String -> r -> r
setHeaderBS :: HasHeaders r => ByteString -> ByteString -> r -> r
setHeaderUnsafe :: HasHeaders r => ByteString -> HeaderPair -> r -> r
addHeader :: HasHeaders r => String -> String -> r -> r
addHeaderBS :: HasHeaders r => ByteString -> ByteString -> r -> r
addHeaderUnsafe :: HasHeaders r => ByteString -> HeaderPair -> r -> r
setRsCode :: Monad m => Int -> Response -> m Response
data Conf = Conf {
port :: Int
validator :: Maybe (Response -> IO Response)
}
nullConf :: Conf
result :: Int -> String -> Response
resultBS :: Int -> ByteString -> Response
redirect :: ToSURI s => Int -> s -> Response -> Response
data RsFlags = RsFlags {
rsfContentLength :: Bool
}
nullRsFlags :: RsFlags
noContentLength :: Response -> Response
data Version = Version Int Int
data Method
= GET
| HEAD
| POST
| PUT
| DELETE
| TRACE
| OPTIONS
| CONNECT
type Headers = Map ByteString HeaderPair
continueHTTP :: Request -> Response -> Bool
type Host = (String, Int)
data ContentType = ContentType {
ctType :: String
ctSubtype :: String
ctParameters :: [(String, String)]
}
Documentation
data Request Source
Constructors
Request
rqMethod :: Method
rqPaths :: [String]
rqUri :: String
rqQuery :: String
rqInputs :: [(String, Input)]
rqCookies :: [(String, Cookie)]
rqVersion :: Version
rqHeaders :: Headers
rqBody :: RqBody
rqPeer :: Host
show/hide Instances
data Response Source
Constructors
Response
rsCode :: Int
rsHeaders :: Headers
rsFlags :: RsFlags
rsBody :: ByteString
rsValidator :: Maybe (Response -> IO Response)
show/hide Instances
newtype RqBody Source
Constructors
Body ByteString
show/hide Instances
data Input Source
Constructors
Input
inputValue :: ByteString
inputFilename :: Maybe String
inputContentType :: ContentType
show/hide Instances
data HeaderPair Source
Constructors
HeaderPair
hName :: ByteString
hValue :: [ByteString]
show/hide Instances
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
port :: IntPort for the server to listen on.
validator :: Maybe (Response -> IO Response)
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.
redirect :: ToSURI s => Int -> s -> Response -> ResponseSource
Sets the Response's status code to the given Int and redirects to the given URI
data RsFlags Source
Result flags
Constructors
RsFlags
rsfContentLength :: Boolwhether a content-length header will be added to the result.
show/hide Instances
nullRsFlags :: RsFlagsSource
Default RsFlags that will include the content-length header
noContentLength :: Response -> ResponseSource
Don't display a Content-Lenght field for the Result.
data Version Source
HTTP version
Constructors
Version Int Int
show/hide Instances
data Method Source
HTTP request method
Constructors
GET
HEAD
POST
PUT
DELETE
TRACE
OPTIONS
CONNECT
show/hide Instances
type Headers = Map ByteString HeaderPairSource
Combined headers.
continueHTTP :: Request -> Response -> BoolSource
Should the connection be used for further messages after this. | isHTTP1_0 && hasKeepAlive || isHTTP1_1 && hasNotConnectionClose
type Host = (String, Int)Source
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
ctType :: StringThe top-level media type, the general type of the data. Common examples are "text", "image", "audio", "video", "multipart", and "application".
ctSubtype :: StringThe 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").
show/hide Instances
Produced by Haddock version 2.4.2