Hugh Perkins wrote:
Here you go:

module SimpleCgiServer
   where

import IO
import Char
import Network
import Control.Monad
import System.Process

listensocket = 2000

main = withSocketsDo $ do socket <- listenOn (PortNumber listensocket)
mapM_ (\_ -> handleconnection socket) (iterate (id) ())
                          sClose socket

handleconnection socket = do (handle,hostname,portnumber) <- accept socket
putStrLn (show(hostname) ++ " " ++ show(portnumber))
                             hSetBuffering handle LineBuffering
                             line <- hGetLine handle
                             let filename = drop( length("GET /") ) line
                             htmltoreturn <- runprocess filename
                             hPutStr handle htmltoreturn

runprocess filename = do (stdin,stdout,stderr,processhandle) <- runInteractiveCommand filename
                         waitForProcess processhandle
                         contents <- hGetContents stdout
                         return contents

Thanks for trying - but that doesn't actually work. (For starters, you need to prepend the HTTP status code to the data from the CGI script...)



Actually, as it turns out, the script I want to test needs to accept POST data, and the parsing is really quite complicated, and I want it to not crash out if I type the URL wrong, and...

Basically, the more I look at this, the more I realise that it really truely *is* going to be faster to just use a real web server. I thought I could just implement a tiny subset of it to get a working system, but it turns out the subset I need isn't so tiny...

Sorry guys.

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to