module Network.HTTP.Stream
( module Network.Stream
, simpleHTTP
, simpleHTTP_
, sendHTTP
, sendHTTP_notify
, receiveHTTP
, respondHTTP
) where
import Network.Stream
import Network.StreamDebugger (debugStream)
import Network.TCP (openTCPPort)
import Network.BufferType ( stringBufferOp )
import Network.HTTP.Base
import Network.HTTP.Headers
import Network.HTTP.Utils ( trim )
import Data.Char (toLower)
import Data.Maybe (fromMaybe)
import Control.Exception (onException)
import Control.Monad (when)
debug :: Bool
debug = False
httpLogFile :: String
httpLogFile = "http-debug.log"
simpleHTTP :: Request_String -> IO (Result Response_String)
simpleHTTP r = do
auth <- getAuth r
c <- openTCPPort (host auth) (fromMaybe 80 (port auth))
simpleHTTP_ c r
simpleHTTP_ :: Stream s => s -> Request_String -> IO (Result Response_String)
simpleHTTP_ s r
| not debug = sendHTTP s r
| otherwise = do
s' <- debugStream httpLogFile s
sendHTTP s' r
sendHTTP :: Stream s => s -> Request_String -> IO (Result Response_String)
sendHTTP conn rq = sendHTTP_notify conn rq (return ())
sendHTTP_notify :: Stream s => s -> Request_String -> IO () -> IO (Result Response_String)
sendHTTP_notify conn rq onSendComplete = do
when providedClose $ (closeOnEnd conn True)
onException (sendMain conn rq onSendComplete)
(close conn)
where
providedClose = findConnClose (rqHeaders rq)
sendMain :: Stream s => s -> Request_String -> IO () -> IO (Result Response_String)
sendMain conn rqst onSendComplete = do
_ <- writeBlock conn (show rqst)
_ <- writeBlock conn (rqBody rqst)
onSendComplete
rsp <- getResponseHead conn
switchResponse conn True False rsp rqst
getResponseHead :: Stream s => s -> IO (Result ResponseData)
getResponseHead conn = do
lor <- readTillEmpty1 stringBufferOp (readLine conn)
return $ lor >>= parseResponseHead
switchResponse :: Stream s
=> s
-> Bool
-> Bool
-> Result ResponseData
-> Request_String
-> IO (Result Response_String)
switchResponse _ _ _ (Left e) _ = return (Left e)
switchResponse conn allow_retry bdy_sent (Right (cd,rn,hdrs)) rqst =
case matchResponse (rqMethod rqst) cd of
Continue
| not bdy_sent ->
do { val <- writeBlock conn (rqBody rqst)
; case val of
Left e -> return (Left e)
Right _ ->
do { rsp <- getResponseHead conn
; switchResponse conn allow_retry True rsp rqst
}
}
| otherwise ->
do { rsp <- getResponseHead conn
; switchResponse conn allow_retry bdy_sent rsp rqst
}
Retry ->
do {
_ <- writeBlock conn (show rqst ++ rqBody rqst)
; rsp <- getResponseHead conn
; switchResponse conn False bdy_sent rsp rqst
}
Done -> do
when (findConnClose hdrs)
(closeOnEnd conn True)
return (Right $ Response cd rn hdrs "")
DieHorribly str -> do
close conn
return $ responseParseError "sendHTTP" ("Invalid response: " ++ str)
ExpectEntity ->
let tc = lookupHeader HdrTransferEncoding hdrs
cl = lookupHeader HdrContentLength hdrs
in
do { rslt <- case tc of
Nothing ->
case cl of
Just x -> linearTransfer (readBlock conn) (read x :: Int)
Nothing -> hopefulTransfer stringBufferOp (readLine conn) []
Just x ->
case map toLower (trim x) of
"chunked" -> chunkedTransfer stringBufferOp
(readLine conn) (readBlock conn)
_ -> uglyDeathTransfer "sendHTTP"
; case rslt of
Left e -> close conn >> return (Left e)
Right (ftrs,bdy) -> do
when (findConnClose (hdrs++ftrs))
(closeOnEnd conn True)
return (Right (Response cd rn (hdrs++ftrs) bdy))
}
receiveHTTP :: Stream s => s -> IO (Result Request_String)
receiveHTTP conn = getRequestHead >>= processRequest
where
getRequestHead :: IO (Result RequestData)
getRequestHead =
do { lor <- readTillEmpty1 stringBufferOp (readLine conn)
; return $ lor >>= parseRequestHead
}
processRequest (Left e) = return $ Left e
processRequest (Right (rm,uri,hdrs)) =
do
let tc = lookupHeader HdrTransferEncoding hdrs
cl = lookupHeader HdrContentLength hdrs
rslt <- case tc of
Nothing ->
case cl of
Just x -> linearTransfer (readBlock conn) (read x :: Int)
Nothing -> return (Right ([], ""))
Just x ->
case map toLower (trim x) of
"chunked" -> chunkedTransfer stringBufferOp
(readLine conn) (readBlock conn)
_ -> uglyDeathTransfer "receiveHTTP"
return $ do
(ftrs,bdy) <- rslt
return (Request uri rm (hdrs++ftrs) bdy)
respondHTTP :: Stream s => s -> Response_String -> IO ()
respondHTTP conn rsp = do
_ <- writeBlock conn (show rsp)
_ <- writeBlock conn (rspBody rsp)
return ()