-- |
-- Module:     Network.IHttp.Response
-- Copyright:  (c) 2010 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez <es@ertes.de>
-- Stability:  experimental
--
-- Iteratees for response.

module Network.IHttp.Response
    ( -- * Iteratees
      response,
      responseLine
    )
    where

import Data.ByteString (ByteString)
import Data.Enumerator as E
import Data.Enumerator.List as EL
import Network.IHttp.Header
import Network.IHttp.Parsers
import Network.IHttp.Tools
import Network.IHttp.Types


-- | Get the next full response from a 'netLinesEmpty'-splitted byte
-- stream.  If the response is invalid or the stream ends prematurely an
-- iteratee error is thrown.  The first 'Int' specifies the maximum
-- header content length.  The second 'Int' specifies the maximum number
-- of headers.  Excess data is truncated safely in constant space.

response :: Monad m => Int -> Int -> Iteratee ByteString m Response
response maxHeadLine maxHeaders = do
    req <- responseLine
    headers <- httpHeaders maxHeadLine maxHeaders
    return req { responseHeaders = headers }


-- | Get the next response line form 'netLinesEmpty'-splitted stream.
-- If the response line is invalid or the stream ended prematurely, then
-- an iteratee error is thrown.

responseLine :: Monad m => Iteratee ByteString m Response
responseLine =
    EL.head
    >>= maybe (throwError $ InvalidResponseError "Premature end of stream") return
    >>= parseIter responseLineP InvalidResponseError