-- | -- Module: Network.IHttp.Types -- Copyright: (c) 2010 Ertugrul Soeylemez -- License: BSD3 -- Maintainer: Ertugrul Soeylemez -- Stability: beta -- -- Types for ihttp. {-# LANGUAGE DeriveDataTypeable #-} module Network.IHttp.Types ( -- * Protocol data HeaderMap, HttpMethod(..), HttpVersion(..), Request(..), Response(..), -- * Miscellaneous types HttpError(..) ) where import Control.Exception as Ex import Data.ByteString (ByteString) import Data.Map (Map) import Data.Typeable -- | Map of HTTP headers. type HeaderMap = Map ByteString ByteString -- | HTTP error. data HttpError -- | Invalid headers from client/server. = InvalidHeaderError { httpErrorMessage :: String } -- | Invalid requests from client. | InvalidRequestError { httpErrorMessage :: String } -- | Invalid responses from server. | InvalidResponseError { httpErrorMessage :: String } -- | Unsupported HTTP version. | UnsupportedVersionError { httpErrorMessage :: String } deriving (Eq, Typeable) instance Exception HttpError instance Show HttpError where show (InvalidHeaderError msg) = "Invalid HTTP header: " ++ msg show (InvalidRequestError msg) = "Invalid HTTP request: " ++ msg show (InvalidResponseError msg) = "Invalid HTTP response: " ++ msg show (UnsupportedVersionError msg) = "Unsupported HTTP version: " ++ msg -- | HTTP request method. data HttpMethod = ConnectMethod -- ^ CONNECT | DeleteMethod -- ^ DELETE | GetMethod -- ^ GET | HeadMethod -- ^ HEAD | OptionsMethod -- ^ OPTIONS | PatchMethod -- ^ PATCH | PostMethod -- ^ POST | PutMethod -- ^ PUT | TraceMethod -- ^ TRACE | XMethod ByteString -- ^ Methods this library doesn't know. deriving (Eq, Read, Show) -- | HTTP protocol version. data HttpVersion = Http1_0 -- ^ Version 1.0 of HTTP. | Http1_1 -- ^ Version 1.1 of HTTP. deriving (Eq, Ord, Read, Show) -- | HTTP request line with status code. data Request = Request { requestHeaders :: HeaderMap, -- ^ Request headers. requestMethod :: HttpMethod, -- ^ Request method. requestUri :: ByteString, -- ^ Request URI. requestVersion :: HttpVersion -- ^ HTTP version of request. } deriving (Eq, Read, Show) -- | HTTP response line with the status code. data Response = Response { responseCode :: Int, -- ^ HTTP response code. responseHeaders :: HeaderMap, -- ^ Response headers. responseMessage :: ByteString, -- ^ Response message. responseVersion :: HttpVersion -- ^ Protocol version of response. } deriving (Eq, Read, Show)