[Haskell-cafe] cgi liftM liftIO
Adrian Neumann
aneumann at inf.fu-berlin.de
Sat Jun 14 02:05:48 EDT 2008
I think you need to put liftIO in front of the IO actions you want to
do inside the CGI Monad. Like in this example
> http://www.haskell.org/haskellwiki/
Practical_web_programming_in_Haskell#File_uploads
(Why did I need to use google to find that? The wiki search in awful.
Searching for CGI returns nothing, whereas with google the above is
the first hit.)
Am 13.06.2008 um 15:41 schrieb Cetin Sert:
> 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?
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
-------------- next part --------------
A non-text attachment was scrubbed...
Name: PGP.sig
Type: application/pgp-signature
Size: 194 bytes
Desc: Signierter Teil der Nachricht
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20080614/555be2b5/PGP-0001.bin
More information about the Haskell-Cafe
mailing list