HAppS-Server-0.9.2.1: Web related tools and services.ContentsIndex
HAppS.Server.HTTP.Types
Synopsis
data Request = Request {
rqMethod :: Method
rqPaths :: [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
}
newtype RqBody = Body ByteString
data Input = Input {
inputValue :: ByteString
inputFilename :: Maybe String
inputContentType :: ContentType
}
data HeaderPair = HeaderPair {
hName :: ByteString
hValue :: [ByteString]
}
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
data Conf = Conf {
port :: Int
}
result :: Int -> String -> Response
resultBS :: Int -> ByteString -> Response
redirect :: ToSURI s => Int -> s -> Response -> Response
data RsFlags = RsFlags {
rsfContentLength :: Bool
}
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
Constructors
Request
rqMethod :: Method
rqPaths :: [String]
rqQuery :: String
rqInputs :: [(String, Input)]
rqCookies :: [(String, Cookie)]
rqVersion :: Version
rqHeaders :: Headers
rqBody :: RqBody
rqPeer :: Host
show/hide Instances
data Response
Constructors
Response
rsCode :: Int
rsHeaders :: Headers
rsFlags :: RsFlags
rsBody :: ByteString
show/hide Instances
newtype RqBody
Constructors
Body ByteString
show/hide Instances
data Input
Constructors
Input
inputValue :: ByteString
inputFilename :: Maybe String
inputContentType :: ContentType
show/hide Instances
data HeaderPair
Constructors
HeaderPair
hName :: ByteString
hValue :: [ByteString]
show/hide Instances
mkHeaders :: [(String, String)] -> Headers
getHeader :: HasHeaders r => String -> r -> Maybe ByteString
Lookup header value. Key is case-insensitive.
getHeaderBS :: HasHeaders r => ByteString -> r -> Maybe ByteString
Lookup header value. Key is a case-insensitive bytestring.
getHeaderUnsafe :: HasHeaders r => ByteString -> r -> Maybe ByteString
Lookup header value with a case-sensitive key. The key must be lowercase.
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
data Conf
HTTP configuration
Constructors
Conf
port :: IntPort for the server to listen on.
show/hide Instances
result :: Int -> String -> Response
resultBS :: Int -> ByteString -> Response
redirect :: ToSURI s => Int -> s -> Response -> Response
data RsFlags
Result flags
Constructors
RsFlags
rsfContentLength :: Boolwhether a content-length header will be added to the result.
show/hide Instances
noContentLength :: Response -> Response
Don't display a Content-Lenght field for the Result.
data Version
HTTP version
Constructors
Version Int Int
show/hide Instances
data Method
HTTP request method
Constructors
GET
HEAD
POST
PUT
DELETE
TRACE
OPTIONS
CONNECT
show/hide Instances
type Headers = Map ByteString HeaderPair
Combined headers.
continueHTTP :: Request -> Response -> Bool
Should the connection be used for further messages after this. | isHTTP1_0 && hasKeepAlive || isHTTP1_1 && hasNotConnectionClose
type Host = (String, Int)
data ContentType
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.1.0