-- |
-- Module:     Network.IHttp.Simple
-- Copyright:  (c) 2010 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez <es@ertes.de>
-- Stability:  beta
--
-- Simple interface to the HTTP iteratees.

module Network.IHttp.Simple
    ( -- * Types
      HttpConfig(..),
      defHttpConfig,

      -- * Iteratees
      getRequest,
      getResponse,
      httpRequest
    )
    where

import Control.ContStuff
import Data.ByteString (ByteString)
import Data.Enumerator as E
import Data.Enumerator.NetLines
import Network.IHttp.Request
import Network.IHttp.Response
import Network.IHttp.Types
import System.IO


-- | HTTP iteratees configuration.

data HttpConfig =
    HttpConfig {
      httpMaxLine          :: Int,  -- ^ Maximum protocol line length.
      httpMaxHeaderContent :: Int,  -- ^ Maximum header content length.
      httpMaxHeaders       :: Int,  -- ^ Maximum number of headers.
      httpTimeout          :: Int   -- ^ Write timeout in milliseconds.
    }


-- | Default HTTP iteratee configuration.  Other than in very special
-- applications you should never need to change these defaults.

defHttpConfig :: HttpConfig
defHttpConfig =
    HttpConfig { httpMaxLine = 1024,
                 httpMaxHeaderContent = 8192,
                 httpMaxHeaders = 128,
                 httpTimeout = 30000 }


-- | Get the next full request from the given raw byte stream.

getRequest :: Monad m => HttpConfig -> Iteratee ByteString m Request
getRequest cfg =
    joinI $ netLinesEmpty (httpMaxLine cfg) $$
    request (httpMaxHeaderContent cfg) (httpMaxHeaders cfg)


-- | Get the next full response from the given raw byte stream.

getResponse :: Monad m => HttpConfig -> Iteratee ByteString m Response
getResponse cfg =
    joinI $ netLinesEmpty (httpMaxLine cfg) $$
    response (httpMaxHeaderContent cfg) (httpMaxHeaders cfg)


-- | Send a request to the given output handle and return its response.

httpRequest ::
    MonadIO m =>
    HttpConfig -> Handle -> Request -> Iteratee ByteString m Response
httpRequest cfg h req = do
    tryIO . run_ $ enumRequest req $$ iterHandleTimeout (httpTimeout cfg) h
    getResponse cfg