[Haskell-cafe] Network.CGI -- practical web programming example.

Edward Ing edward.ing at gmail.com
Sat Jun 27 20:07:54 EDT 2009


I am somewhat new to haskell. It is amazing that I can actually write
a CGI program using Network.CGI without really being comfortable with
the Haskell type system. Especially when it involves monad
transformations.
So I decided that I better understand this. I looked at the Practical
Web Programming examples to try to understand what is going on. I came
up with a problem that might demonstrate my misunderstanding. I am
wondering if you can answer questions I have. Code 1 is the example
from PWP, Code 2 is my variation and it works so I am stumped by what
the liftM is required.

code 1>>>
#!/usr/bin/runghc
import Network.CGI
import Text.XHtml

import qualified Data.ByteString.Lazy as BS

import Control.Monad (liftM)
import Data.Maybe (fromJust)

uploadDir = "../upload"

fileForm = form ! [method "post", enctype "multipart/form-data"]
            << [afile "file", submit "" "Upload"]
saveFile n =
   do          cont <- (liftM fromJust) $ getInputFPS "file"
        let f = uploadDir ++ "/" ++ basename n
        liftIO $ BS.writeFile f cont
        return $ paragraph << ("Saved as " +++ anchor ! [href f] << f +++ ".")

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

basename = reverse . takeWhile (`notElem` "/\\") . reverse

cgiMain =
   do mn <- getInputFilename "file"
      h <- maybe (return fileForm) saveFile mn
      output $ renderHtml $ page "Upload example" h

main = runCGI $ handleErrors cgiMain

Code 2 (modifier) >>>

import Network.CGI
import Text.XHtml

import qualified Data.ByteString.Lazy as BS

import Control.Monad (liftM)
import Data.Maybe (fromJust)

uploadDir = "../upload"

fileForm = form ! [method "post", enctype "multipart/form-data"]
            << [afile "file", submit "" "Upload"]
saveFile n =
do   cont <- getInputFPS "file"
       let f = uploadDir ++ "/" ++ basename n
      liftIO $ BS.writeFile f (fromJust cont)
      return $ paragraph << ("Saved as " +++ anchor ! [href f] << f +++ ".")

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

basename = reverse . takeWhile (`notElem` "/\\") . reverse

cgiMain =
   do mn <- getInputFilename "file"
      h <- maybe (return fileForm) saveFile mn
      output $ renderHtml $ page "Upload example" h

main = runCGI $ handleErrors cgiMain



Questions ===

1) Why did the author choose to insert "liftM" in function saveFile?
It doesn't seem necessary in my version.

2) My background mainly is Java but here is my understanding of Monad
Transforms. The CGIT m type carries around with it the CGI Request
context and response contexts. The transformations (lifts) is similar
to casting so that you can use the functions for specific
manifestations but it also encapsulates the data. Is this correct?


Edward


More information about the Haskell-Cafe mailing list