
Hi. I want to write a reverse proxy like perlbal to practive haskell. Now I just write a very simple script to forward any request to www.google.com. but it dosn't work. I run command ' runhaskell Proxy.hs' and 'wget http://localhost:8080/'. but wget just wait forever and runhaskkell can get request. when I break wget, the 'runhaskell' can print response returned from www.google.com. why? module Main where import System.Posix.Process import Network import Prelude hiding (putStr) import System.IO hiding (hGetContents, putStr) import Control.Concurrent import System.Posix.Signals import Data.ByteString.Lazy.Char8 (hGetContents, hPut, putStr,hGet,cons) listenPort = PortNumber 8080 connectToHost = "208.67.219.230" connectToPort = PortNumber 80 main :: IO () main = do hSetBuffering stdout NoBuffering socket <- listenOn listenPort let doLoop = do (hdl, _, _) <- accept socket forkIO $ processRequest hdl doLoop doLoop processRequest :: Handle -> IO () processRequest hRequest = do installHandler sigPIPE Ignore Nothing; hSetBuffering hRequest NoBuffering hSetBuffering stdout NoBuffering request <- hGetContents hRequest putStr $ '>' `cons` (' ' `cons` request) hResponse <- connectTo connectToHost connectToPort hSetBuffering hResponse NoBuffering hPut hResponse request response <- hGetContents hResponse putStr $ '<' `cons` (' ' `cons` response) hPut hRequest response hClose hRequest hClose hResponse -- Thanks & Regards Changying Li

On 2008 August 08 Friday, Changying Li wrote:
I want to write a reverse proxy like perlbal to practive haskell. Now I just write a very simple script to forward any request to www.google.com.
but it dosn't work. I run command ' runhaskell Proxy.hs' and 'wget http://localhost:8080/'. but wget just wait forever and runhaskkell can get request. when I break wget, the 'runhaskell' can print response returned from www.google.com.
The problem is with
request <- hGetContents hRequest which blocks until wget closes the connection. Using lazy bytestrings just defers the problem slightly. Your processRequest blocks when the 'request' string is used.
For some insight into how this can be avoided, see hGetBufNonBlocking. I'm not familiar enough with the Haskell libraries to point you to the ideal solution.

thanks. I know how to do it. I should treat it as a stream. -- Thanks & Regards Changying Li
participants (2)
-
Changying Li
-
Scott Turner