Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Request = Request {}
- data Response
- newtype RqBody = Body {
- unBody :: ByteString
- data Input = Input {}
- data HeaderPair = HeaderPair {
- hName :: ByteString
- hValue :: [ByteString]
- takeRequestBody :: MonadIO m => Request -> m (Maybe RqBody)
- readInputsBody :: Request -> IO (Maybe [(String, Input)])
- 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
- type LogAccess time = String -> String -> time -> String -> Int -> Integer -> String -> String -> IO ()
- logMAccess :: forall t. FormatTime t => LogAccess t
- data Conf = Conf {}
- nullConf :: Conf
- result :: Int -> String -> Response
- resultBS :: Int -> ByteString -> Response
- redirect :: ToSURI s => Int -> s -> Response -> Response
- isHTTP1_0 :: Request -> Bool
- isHTTP1_1 :: Request -> Bool
- data RsFlags = RsFlags {}
- nullRsFlags :: RsFlags
- contentLength :: Response -> Response
- chunked :: Response -> Response
- noContentLength :: Response -> Response
- data HttpVersion = HttpVersion Int Int
- data Length
- data Method
- canHaveBody :: Method -> Bool
- type Headers = Map ByteString HeaderPair
- continueHTTP :: Request -> Response -> Bool
- type Host = (String, Int)
- data ContentType = ContentType {}
- readDec' :: (Num a, Eq a) => String -> a
- fromReadS :: [(a, String)] -> Maybe a
- readM :: (Monad m, Read t) => String -> m t
- class FromReqURI a where
- fromReqURI :: String -> Maybe a
- showRsValidator :: Maybe (Response -> IO Response) -> String
- data EscapeHTTP = EscapeHTTP (TimeoutIO -> IO ())
Documentation
an HTTP request
Request | |
|
an HTTP Response
Instances
Show Response Source # | |
Error Response Source # | |
ToMessage Response Source # | |
Defined in Happstack.Server.Response toContentType :: Response -> ByteString Source # toMessage :: Response -> ByteString Source # toResponse :: Response -> Response Source # | |
Monad m => WebMonad Response (WebT m) Source # | |
Defined in Happstack.Server.Internal.Monads finishWith :: Response -> WebT m b Source # | |
Monad m => WebMonad Response (ServerPartT m) Source # | |
Defined in Happstack.Server.Internal.Monads finishWith :: Response -> ServerPartT m b Source # | |
Monad m => FilterMonad Response (WebT m) Source # | |
Monad m => FilterMonad Response (ServerPartT m) Source # | |
Defined in Happstack.Server.Internal.Monads setFilter :: (Response -> Response) -> ServerPartT m () Source # composeFilter :: (Response -> Response) -> ServerPartT m () Source # getFilter :: ServerPartT m b -> ServerPartT m (b, Response -> Response) Source # |
The body of an HTTP Request
Body | |
|
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
HeaderPair | |
|
Instances
Read HeaderPair Source # | |
Defined in Happstack.Server.Internal.Types readsPrec :: Int -> ReadS HeaderPair # readList :: ReadS [HeaderPair] # readPrec :: ReadPrec HeaderPair # readListPrec :: ReadPrec [HeaderPair] # | |
Show HeaderPair Source # | |
Defined in Happstack.Server.Internal.Types 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
HTTP configuration
Conf | |
|
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
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
Instances
Eq HttpVersion Source # | |
Defined in Happstack.Server.Internal.Types (==) :: HttpVersion -> HttpVersion -> Bool # (/=) :: HttpVersion -> HttpVersion -> Bool # | |
Read HttpVersion Source # | |
Defined in Happstack.Server.Internal.Types readsPrec :: Int -> ReadS HttpVersion # readList :: ReadS [HttpVersion] # readPrec :: ReadPrec HttpVersion # readListPrec :: ReadPrec [HttpVersion] # | |
Show HttpVersion Source # | |
Defined in Happstack.Server.Internal.Types showsPrec :: Int -> HttpVersion -> ShowS # show :: HttpVersion -> String # showList :: [HttpVersion] -> ShowS # |
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
ContentLength | automatically add a |
TransferEncodingChunked | do not add a |
NoContentLength | do not set |
HTTP request method
Instances
Eq Method Source # | |
Data Method Source # | |
Defined in Happstack.Server.Internal.Types 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 # | |
Read Method Source # | |
Show Method Source # | |
MatchMethod Method Source # | |
Defined in Happstack.Server.Routing | |
MatchMethod [Method] Source # | |
Defined in Happstack.Server.Routing | |
MatchMethod (Method -> Bool) Source # | |
Defined in Happstack.Server.Routing |
canHaveBody :: Method -> Bool Source #
Does the method support a message body?
For extension methods, we assume yes.
= 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.
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.
ContentType | |
|
Instances
Eq ContentType Source # | |
Defined in Happstack.Server.Internal.RFC822Headers (==) :: ContentType -> ContentType -> Bool # (/=) :: ContentType -> ContentType -> Bool # | |
Ord ContentType Source # | |
Defined in Happstack.Server.Internal.RFC822Headers compare :: ContentType -> ContentType -> Ordering # (<) :: ContentType -> ContentType -> Bool # (<=) :: ContentType -> ContentType -> Bool # (>) :: ContentType -> ContentType -> Bool # (>=) :: ContentType -> ContentType -> Bool # max :: ContentType -> ContentType -> ContentType # min :: ContentType -> ContentType -> ContentType # | |
Read ContentType Source # | |
Defined in Happstack.Server.Internal.RFC822Headers readsPrec :: Int -> ReadS ContentType # readList :: ReadS [ContentType] # readPrec :: ReadPrec ContentType # readListPrec :: ReadPrec [ContentType] # | |
Show ContentType Source # | |
Defined in Happstack.Server.Internal.RFC822Headers showsPrec :: Int -> ContentType -> ShowS # show :: ContentType -> String # showList :: [ContentType] -> ShowS # |
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
fromReqURI :: String -> Maybe a Source #
Instances
data EscapeHTTP Source #
Escape from the HTTP world and get direct access to the underlying TimeoutIO
functions
EscapeHTTP (TimeoutIO -> IO ()) |
Instances
Show EscapeHTTP Source # | |
Defined in Happstack.Server.Internal.Types showsPrec :: Int -> EscapeHTTP -> ShowS # show :: EscapeHTTP -> String # showList :: [EscapeHTTP] -> ShowS # | |
Exception EscapeHTTP Source # | |
Defined in Happstack.Server.Internal.Types toException :: EscapeHTTP -> SomeException # fromException :: SomeException -> Maybe EscapeHTTP # displayException :: EscapeHTTP -> String # |