module Network.CGI.Compat (
Html, wrapper, pwrapper, connectToCGIScript
) where
import Control.Concurrent (forkIO)
import Control.Exception.Extensible as Exception (SomeException,throw,catch,finally)
import Control.Monad (unless)
import Control.Monad.Trans (MonadIO, liftIO)
import qualified Data.Map as Map
import Network (PortID, Socket, listenOn, connectTo)
import Network.Socket as Socket (SockAddr(SockAddrInet), accept, socketToHandle)
import System.IO (Handle, hPutStrLn, stdin, stdout,
hGetLine, hClose, IOMode(ReadWriteMode))
import System.IO.Error (isEOFError)
import qualified Data.ByteString.Lazy.Char8 as BS
import Data.ByteString.Lazy.Char8 (ByteString)
import Text.XHtml (Html, renderHtml)
import Network.CGI.Protocol
wrapper :: ([(String,String)] -> IO Html) -> IO ()
wrapper = run stdin stdout
pwrapper :: PortID
-> ([(String,String)] -> IO Html)
-> IO ()
pwrapper pid f = do sock <- listenOn pid
acceptConnections fn sock
where fn h = run h h f
acceptConnections :: (Handle -> IO ()) -> Socket -> IO ()
acceptConnections fn sock = do
(h, SockAddrInet _ _) <- accept' sock
_ <- forkIO (fn h `finally` (hClose h))
acceptConnections fn sock
accept' :: Socket
-> IO (Handle,SockAddr)
accept' sock = do
(sock', addr) <- Socket.accept sock
handle <- socketToHandle sock' ReadWriteMode
return (handle,addr)
run :: MonadIO m => Handle -> Handle -> ([(String,String)] -> IO Html) -> m ()
run inh outh f =
do env <- getCGIVars
hRunCGI env inh outh f'
where f' req = do let vs = Map.toList (cgiVars req)
is = [ (n,BS.unpack (inputValue i)) | (n,i) <- cgiInputs req ]
html <- liftIO (f (vs++is))
return ([], CGIOutput $ BS.pack $ renderHtml html)
connectToCGIScript :: String -> PortID -> IO ()
connectToCGIScript host portId
= do env <- getCGIVars
input <- BS.hGetContents stdin
let str = getRequestInput env input
h <- connectTo host portId
`Exception.catch`
(\ e -> abort "Cannot connect to CGI daemon." e)
BS.hPut h str >> hPutStrLn h ""
(sendBack h `finally` hClose h)
`Exception.catch` (\e -> unless (isEOFError e) (ioError e))
getRequestInput :: [(String,String)]
-> ByteString
-> ByteString
getRequestInput env req =
case lookup "REQUEST_METHOD" env of
Just "POST" -> takeInput env req
_ -> maybe BS.empty BS.pack (lookup "QUERY_STRING" env)
abort :: String -> SomeException -> IO a
abort msg e =
do putStrLn ("Content-type: text/html\n\n" ++
"<html><body>" ++ msg ++ "</body></html>")
throw e
sendBack :: Handle -> IO ()
sendBack h = do s <- hGetLine h
putStrLn s
sendBack h