[Haskell-cafe] cgi liftM liftIO
Cetin Sert
cetin.sert at gmail.com
Fri Jun 13 09:41:29 EDT 2008
Hi,
Could someone please care to explain what I am doing wrong below in cgiMain2
and how can I fix it?
./Main.hs:25:15:
No instance for (MonadCGI IO)
arising from a use of `output' at ./Main.hs:25:15-20
Possible fix: add an instance declaration for (MonadCGI IO)
In the first argument of `($)', namely `output'
In the expression: output $ renderHtml $ page "import" fileForm
In the definition of `upload':
upload = output $ renderHtml $ page "import" fileForm
./Main.hs:57:29:
Couldn't match expected type `CGI CGIResult'
against inferred type `IO CGIResult'
In the first argument of `handleErrors', namely `cgiMain2'
In the second argument of `($)', namely `handleErrors cgiMain2'
In the expression: runCGI $ handleErrors cgiMain2
import IO
import Network.CGI
import Text.XHtml
import qualified Data.ByteString.Lazy as BS
import Control.Monad (liftM)
import Data.Maybe (fromJust)
import Interact
fileForm = form ! [method "post", enctype "multipart/form-data"] <<
[afile "file", submit "" "Upload"]
page t b = header << thetitle << t +++ body << b
cgiMain1 = do
getInputFPS "file" ↠ λms → maybe upload contents ms ↠ return
where
upload = output $ renderHtml $ page "import" fileForm
contents = outputFPS
cgiMain2 = do
getInputFPS "file" ↠ λms → maybe upload contents ms ↠ return
where
upload = output $ renderHtml $ page "import" fileForm
contents = λs → do
(i,o,h,_) ← runUnzip
BS.hPutStr i s
c ← BS.hGetContents o
outputFPS c
{-
(i,o,h,_) ← runUnzip
BS.hPutStr i s
BS.hGetContents o ↠ outputFPS
-}
{-
liftM :: (Monad m) => (a1 -> r) -> m a1 -> m r
liftIO :: (MonadIO m) => IO a -> m a
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 +++
".")
-}
runUnzip = runInteractiveCommand "unzip -l /dev/stdin"
main = runCGI $ handleErrors cgiMain2
Best Regards,
Cetin Sert
P/s: what are lifts o_O?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080613/3ab681c2/attachment.htm
More information about the Haskell-Cafe
mailing list