Network.Salvia.Handler.Parser
- hRequestParser :: (HandleM m, RawHttpM Request m, HttpM Request m, MonadIO m) => Int -> (String -> m a) -> m a -> m (Maybe a)
- hResponseParser :: (HandleM m, RawHttpM Response m, HttpM Response m, MonadIO m) => Int -> (String -> m a) -> m a -> m (Maybe a)
- hParser :: (HandleM m, MonadIO m) => (Http d -> m b) -> (String -> Either String (Http d)) -> Int -> (String -> m a) -> m a -> m (Maybe a)
- readNonEmptyLines :: Handle -> IO String
Documentation
Arguments
| :: (HandleM m, RawHttpM Request m, HttpM Request m, MonadIO m) | |
| => Int | Timeout in milliseconds. |
| -> (String -> m a) | The fail handler. |
| -> m a | The success handler. |
| -> m (Maybe a) |
Like the hParser but always parses HTTP Requestss.
Arguments
| :: (HandleM m, MonadIO m) | |
| => (Http d -> m b) | What to do with message. |
| -> (String -> Either String (Http d)) | Custom message parser. |
| -> Int | Timeout in milliseconds. |
| -> (String -> m a) | The fail handler. |
| -> m a | The success handler. |
| -> m (Maybe a) |
The hParser handler is used to parse the raw HTTP message into the
Message data type. This handler is generally used as (one of) the first
handlers in a client or server environment. The first handler argument is
executed when the message is invalid, possibly due to parser errors, and is
parametrized with the error string. The second handler argument is executed
when the message is valid. When the message could not be parsed within the time
specified with the first argument the function silently returns.