[Haskell-cafe] Network.CGI.Compat.pwrapper

Bjorn Bringert bringert at cs.chalmers.se
Mon Feb 12 15:23:13 EST 2007


On Feb 12, 2007, at 14:22 , Gracjan Polak wrote:

> I wanted to setup really simple http server, found  
> Network.CGI.Compat.pwrapper
> and decided it suits my needs. Code:
>
> module Main where
> import Network.CGI
> import Text.XHtml
> import Network
>
> doit vars = do
>     return (body (toHtml (show vars)))
>
> main = withSocketsDo (pwrapper (PortNumber 7777) doit)
>
>
> Pointng any browser to http://127.0.0.1:7777 does not render the  
> page. It seems
> the response headers are broken.
>
> How do I report this bug (trac? something else?).
>
> We might want to either fix it, or just get rid of it, as nobody  
> seems to notice
> the problem :)
>
> $ ghc --version
> The Glorious Glasgow Haskell Compilation System, version 6.6
>
> Tested under WinXP and MacOSX 10.4.9.

Hi Gracjan,

pwrapper is not an HTTP server, though the Haddock comment can make  
you think so. pwrapper allows you to talk *CGI* over a TCP port, but  
I have no idea why anyone would like to do that. The functions in the  
Network.CGI.Compat module are deprecated, and shouldn't be used in  
new code. Even though I'm the maintainer of the cgi package, I don't  
really know what those functions could ever be useful for, and I've  
never seen any code which uses them. In fact, I've now removed the  
Network.CGI.Compat module and uploaded cgi-3001.0.0 to Hackage.

> Another question is: how do I do equivalent functionality without  
> pwrapper?

You can roll you own web server if you want something very simple. If  
you don't want to do that, there is a version of Simon Marlow's  
Haskell Web Server with CGI support [1]. You could also get the  
original HWS [2] and merge it with your program. You might also be  
interested In HAppS [3].

/Björn

[1] http://www.cs.chalmers.se/~bringert/darcs/hws-cgi/
[2] http://darcs.haskell.org/hws/
[3] http://happs.org/


More information about the Haskell-Cafe mailing list