Hi,

I have never used Text.HTML (except for stringToHtmlString) but any code that works as CGI must work as FastCGI with appropriate runFastCGI call. Try not to use nginx, it can't run fastcgi processes as far as I know. I use lighttpd or Apache(mod_fastcgi)+nginx to run fastcgi programs.

On Fri, Jun 11, 2010 at 11:48 AM, Jonas Fager <jonas.fager@gmail.com> wrote:
Hi.

This is probably "I must be blind department"

I have a very basic strip down echo cgi that runs with apache2.

When I try to modfi it to be a FastCGI instead and run it with spawn-fcgi with nginx
It don't behave as expected.
I suppose that the line that don't get any data is mn <-  getInputFPS "file" when running under FastGCI.
So is the code wrong? or have I missed something with the setup?

I can run the example of fastcgi provided in http://mult.ifario.us/p/wiring-haskell-into-a-fastcgi-web-server with no problem.


Description:    Ubuntu 10.04 LTS
2.6.32-22-generic-pae #36-Ubuntu SMP
The Glorious Glasgow Haskell Compilation System, version 6.12.1

+++++
import Control.Concurrent
import Network.CGI
-- import Network.FastCGI
import Text.Html
import qualified Data.ByteString.Lazy as BS
import qualified Data.ByteString.Lazy.Char8 as BS8
import Control.Monad (liftM)
import Data.Maybe (fromJust)
import Char
import Data.List
import System.Time
import qualified Data.ByteString.Char8 as C
import Text.JSON.Generic
import Text.JSON

insertthis fb =  do
  let f = BS8.unpack  fb
  return (f)




fileForm = form ! [method "post", enctype "multipart/form-data"]
             << [textfield "file", submit "" "Upload"]



saveFile cont =
    do r<-liftIO $ insertthis  cont
       return $ paragraph << ("Inserted " ++ (show r))

page t b = header << thetitle << t +++ body << b




test :: CGI CGIResult
test = do setHeader "Content-Type" "text/html; charset=utf-8"
          mn <-  getInputFPS "file"
          h <- maybe (return fileForm) saveFile mn
          output $  renderHtml $ page "Upload" h


main = runCGI $ handleErrors test

--main= runFastCGI $ handleErrors test

+++++

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