gdritter repos shelob / master shelob / src / Network / Shelob / Types.hs
master

Tree @master (Download .tar.gz)

Types.hs @masterraw · history · blame

{-# LANGUAGE BangPatterns #-}

module Network.Shelob.Types where

import qualified Control.Exception as Ex
import           Control.DeepSeq (NFData(..))
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LBS
import           Data.Typeable (Typeable)

data Method
  = MGet
  | MHead
  | MPost
  | MPut
  | MDelete
  | MTrace
  | MOptions
  | MConnect
  | MPatch
  | MOther !BS.ByteString
    deriving (Eq, Show)

instance NFData Method where
  rnf _ = ()

data Header
  = HContentLength !Int
  | Header !BS.ByteString !BS.ByteString
    deriving (Eq, Show)

instance NFData Header where
  rnf (HContentLength v) = rnf v
  rnf (Header k v) = rnf k `seq` rnf v


data Request = Request
  { requestMethod  :: !Method
  , requestPath    :: !BS.ByteString
  , requestHeaders :: ![Header]
  , requestBody    :: !BS.ByteString
  } deriving (Eq, Show)

instance NFData Request where
  rnf (Request m p h b) = rnf m `seq` rnf p `seq` rnf h `seq` rnf b


type ResponseCode = (Int, Int, Int)

data Response = Response
  { responseHeaders :: ![Header]
  , responseCode    :: !ResponseCode
  , responseBody    :: !(Maybe BS.ByteString)
  } deriving (Eq, Show)

instance NFData Response where
  rnf (Response h c b) = rnf h `seq` rnf c `seq` rnf b


-- | This "Connection" abstraction allows us to build on top of
-- arbitrary other connection packages for our HTTP
data Connection = Connection
  { connRead     :: Int -> IO BS.ByteString
  , connReadLine :: IO BS.ByteString
  , connWrite    :: LBS.ByteString -> IO ()
  , connClose    :: IO ()
  }


data HTTPError
  = HTTPError deriving (Typeable, Show)

instance Ex.Exception HTTPError where