
Greetings. Can somebody write a trivial (as in: small) program so I can test my CGI stuff without having to actually install and configure Apache? (Basically, I'd like something I can compile into a small binary, so when I double-click it, it will listen on port 80, and when it gets a HTTP request, it tries to find a program with that name, and run it as a CGI script. And that's all. Nothing fancy; if I want fancy Apache can do a propper job...) Actually, might be a useful thing to have in a library somewhere.

Andrew Coppin on 2007-07-10 21:23:23 +0100:
Can somebody write a trivial (as in: small) program so I can test my CGI stuff without having to actually install and configure Apache?
The Haskell wiki (http://www.haskell.org/) lists several web servers; one appears to fit your needs of being small and able to run CGI. Look under "Applications and libraries" to get started.
Actually, might be a useful thing to have in a library somewhere.
The Haskell wiki also lists several HTTP libraries.

Andrew Coppin wrote:
Greetings.
Can somebody write a trivial (as in: small) program so I can test my CGI stuff without having to actually install and configure Apache?
[...]
You could adapt the TCP server from this tutorial -> http://sequence.complete.org/node/258 Regards, -- View this message in context: http://www.nabble.com/CGI-test-tf4058260.html#a11529701 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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 You can change the portnumber by changing the value of the function "listensocket". This expects you to send it something like "GET /test.bat". It will run test.bat - or whatever filename you sent it - and send the results back down the socket. It's obviously not at all secure, eg we're not filtering things like ".." from the input, so make sure to not publish the port to anywhere insecure (like the Internet).

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.

On Jul 12, 2007, at 19:59 , Andrew Coppin wrote:
Hugh Perkins wrote:
...
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.
As an earlier poster hinted, there is a version of Haskell Web Server that can run CGI programs: http://www.cs.chalmers.se/~bringert/darcs/hws-cgi/ /Björn

Bjorn Bringert wrote:
On Jul 12, 2007, at 19:59 , Andrew Coppin wrote:
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.
As an earlier poster hinted, there is a version of Haskell Web Server that can run CGI programs:
Thanks. I'll take a look...

Andrew Coppin wrote:
Greetings.
Can somebody write a trivial (as in: small) program so I can test my CGI stuff without having to actually install and configure Apache?
(Basically, I'd like something I can compile into a small binary, so when I double-click it, it will listen on port 80, and when it gets a HTTP request, it tries to find a program with that name, and run it as a CGI script. And that's all. Nothing fancy; if I want fancy Apache can do a propper job...)
Actually, might be a useful thing to have in a library somewhere.
About two years ago, I wrote a small httpd that I use to serve stuff. It's able to do CGI as well: http://people.freebsd.org/~ssouhlal/stuff/rephttpd-0.4.hs Feel free to do whatever you want with it (even though the code is not that great). -- Suleiman
participants (6)
-
Alec Berryman
-
Andrew Coppin
-
Bjorn Bringert
-
Hugh Perkins
-
Jim Burton
-
Suleiman Souhlal