Network.CGI -- practical web programming example.

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

Your code examples are:
On Sat, Jun 27, 2009 at 6:07 PM, Edward Ing
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 +++ ".")
Vs.
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 +++ ".")
Consider the line x <- y in a do expression. If y has type M a for some monad M, then x has type a. So, let's say you have a value f :: Maybe Int, and you want to return the Int's stringification if it exists. We can write this in these two ways: do x <- f return (show x) do x <- liftM show f return x liftM :: (a -> b) -> (M a -> M b) for any monad M. That means if you want to apply a function to a value which is currently wrapped in a monad constructor, you need to "lift" it in. liftM takes a function on ordinary values to a function on wrapped values. But *after* you bind, you don't need to lift anymore. Which of the two above styles to choose is a matter of style, and, in my code at least, varies from situation to situation. That said, you can write both of these snippets as "fmap show f" or "show <$> f" (where (<$>) is from Control.Applicative), which is how it would be done in practice. Does that make sense? Luke

On Jun 27, 2009, at 20:07 , Edward Ing wrote:
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 +++ ".")
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 + ++ ".")
1) Why did the author choose to insert "liftM" in function saveFile?
It's because of where fromJust is being called. In yours, it's being used at a place that expects a normal value, so you can just go ahead and use it. The original is applying the fromJust inside of a monadic computation, as indicated by the (<-), so it needs to be lifted. Some Haskell programmers use fmap (because most Monads are also Functors), others use liftM. Both have the same effect: given a monadic computation "m a", "liftM f" turns "f" into a function that operates on the enclosed "a" instead of the entire "m a". -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Brandon S. Allbery KF8NH wrote:
Some Haskell programmers use fmap (because most Monads are also Functors), others use liftM. Both have the same effect: given a monadic computation "m a", "liftM f" turns "f" into a function that operates on the enclosed "a" instead of the entire "m a".
That is, given the theory behind it all, every monad is a functor (note the lower case); from which it follows that liftM == fmap. For historical reasons the Monad typeclass does not require a Functor instance, however, and so it's not the case that every Monad is also a Functor (note the upper case). The function liftM can be defined generically given definitions for return and (>>=), so some prefer to use liftM to avoid the extra Functor dependency. The function fmap can be given specialized definitions due to overloading, so others prefer to use it for efficiency reasons. The (<$>) function is just a symbolic name for fmap. You'll also see the Applicative typeclass for "applicative functors". Applicative does require a Functor instance, which is good. (And actually, every monad is an applicative functor; though the Monad class doesn't require Applicative either.) The function liftA can be defined generically given definitions for pure and (<*>), and liftA == fmap as well. The only reason anyone should use liftA is for defining a Functor instance when they're too lazy to give a specialized implementation. -- Live well, ~wren

On Jul 2, 2009, at 17:59 , wren ng thornton wrote:
Brandon S. Allbery KF8NH wrote:
Some Haskell programmers use fmap (because most Monads are also Functors), others use liftM. Both have the same effect: given a monadic computation "m a", "liftM f" turns "f" into a function that operates on the enclosed "a" instead of the entire "m a".
That is, given the theory behind it all, every monad is a functor (note the lower case); from
Yeh, I decided to bypass the whole "all monads are functors, but for Hysterical Raisins not all Monads are Functors" morass. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
participants (4)
-
Brandon S. Allbery KF8NH
-
Edward Ing
-
Luke Palmer
-
wren ng thornton