Problem compiling a CGI script that needs to write to file during its execution

Please ignore the obvious security holes, as this is not a script meant for public consumption, but some internal testing and prototyping. I would like to write the result of my computation out to a file inside of cgiMain, but the type of the monad inside cgiMain is this odd CGIT IO CGIResult. I tried using liftM on writeFile, but it then complained that "newanns" was a string instead of a list of strings, which I don't understand at all. Here's the code: DeleteAnnotation.hs: -------------------------------------------------------------------------------- import Network.CGI import Annotations import Graphics.Rendering.OpenGL.GL (GLfloat) import Control.Monad (liftM) import Data.List (filter) getInput' v = do x <- getInput v case x of Nothing -> fail "essential variable not found" Just y -> return y cgiMain :: String -> CGI CGIResult cgiMain anns_dot_txt = do ordnl <- (liftM read) $ getInput' "ordinal" let anns = (filter (notequal ordnl) . read $ anns_dot_txt) :: [Annotation] newanns = show anns output $ newanns writeFile "Annotations.txt" $ newanns notequal :: String -> Annotation -> Bool notequal ordnl ann = ordnl == ordinal ann main :: IO () main = do f <- readFile "Annotations.txt" runCGI (handleErrors (cgiMain f)) -------------------------------------------------------------------------------- $ ghc --make DeleteAnnotation DeleteAnnotation.hs:19:2: Couldn't match expected type `CGIT IO CGIResult' against inferred type `IO ()' In the expression: writeFile "Annotations.txt" $ newanns In the expression: do ordnl <- (liftM read) $ getInput' "ordinal" let anns = ... newanns = show anns output $ newanns writeFile "Annotations.txt" $ newanns In the definition of `cgiMain': cgiMain anns_dot_txt = do ordnl <- (liftM read) $ getInput' "ordinal" let anns = ... .... output $ newanns .... If I change writeFile "Annotations.txt" to (liftM (writeFile "Annotations.txt")): $ ghc --make DeleteAnnotation DeleteAnnotation.hs:19:42: Couldn't match expected type `String' against inferred type `Char' Expected type: [String] Inferred type: String In the second argument of `($)', namely `newanns' In the expression: (liftM (writeFile "Annotations.txt")) $ newanns

Hi I had this same problem and I'm not sure my way is correct but I used 'Control.Monad.Trans.liftIO' Here is some code that I am using {- The main program is pretty simple we just run the CGI action. -} main :: IO () main = Cgi.runCGI $ Cgi.handleErrors cgiMain {- To be able to produce graphs which we can then display in the output webpage we require that our main function, that is the one which creates the page be in the IO monad. -} cgiMain :: CGI CGIResult cgiMain = do visitInfo <- getAnalysisData page <- Monad.Trans.liftIO $ createPage visitInfo Cgi.output $ Xhtml.renderHtml page createPage :: Visit -> IO Html createPage ..... blah stuff you don't care about getAnalysisData :: CGI Visit Visit is a data type I've made to hold the information obtained from the page. Hope this helps allan Jefferson Heard wrote:
Please ignore the obvious security holes, as this is not a script meant for public consumption, but some internal testing and prototyping. I would like to write the result of my computation out to a file inside of cgiMain, but the type of the monad inside cgiMain is this odd CGIT IO CGIResult. I tried using liftM on writeFile, but it then complained that "newanns" was a string instead of a list of strings, which I don't understand at all. Here's the code:
DeleteAnnotation.hs:
[snip code] -- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336.

Beautiful, thank you. That worked.
On Tue, Jul 29, 2008 at 12:07 PM, allan
Hi
I had this same problem and I'm not sure my way is correct but I used 'Control.Monad.Trans.liftIO' Here is some code that I am using
{- The main program is pretty simple we just run the CGI action. -} main :: IO () main = Cgi.runCGI $ Cgi.handleErrors cgiMain
{- To be able to produce graphs which we can then display in the output webpage we require that our main function, that is the one which creates the page be in the IO monad. -} cgiMain :: CGI CGIResult cgiMain = do visitInfo <- getAnalysisData page <- Monad.Trans.liftIO $ createPage visitInfo Cgi.output $ Xhtml.renderHtml page
createPage :: Visit -> IO Html createPage ..... blah stuff you don't care about
getAnalysisData :: CGI Visit
Visit is a data type I've made to hold the information obtained from the page.
Hope this helps allan
Jefferson Heard wrote:
Please ignore the obvious security holes, as this is not a script meant for public consumption, but some internal testing and prototyping. I would like to write the result of my computation out to a file inside of cgiMain, but the type of the monad inside cgiMain is this odd CGIT IO CGIResult. I tried using liftM on writeFile, but it then complained that "newanns" was a string instead of a list of strings, which I don't understand at all. Here's the code:
DeleteAnnotation.hs:
[snip code]
-- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336.
-- I try to take things like a crow; war and chaos don't always ruin a picnic, they just mean you have to be careful what you swallow. -- Jessica Edwards

On Tue, Jul 29, 2008 at 8:57 AM, Jefferson Heard
I tried using liftM on writeFile, but it then complained that "newanns" was a string instead of a list of strings, which I don't understand at all.
liftM isn't what you think it is.
liftM :: (a -> b) -> (m a -> m b) which is doing something weird depending how you inserted it: liftM (writeFile "x") :: Monad m => m String -> m (IO ()) which could theoretically have m get forced to be a list as the typechecker tries to figure out how to decipher this mess... liftM (writeFile "x") :: [String] -> [IO ()] or something else weird.
You are looking for either lift or liftIO, from Control.Monad.Trans
lift :: (Monad m, MonadTrans t) => m a -> t m a liftIO :: MonadIO m => IO a -> m a
-- ryan

On Tue, Jul 29, 2008 at 3:48 PM, Ryan Ingram
On Tue, Jul 29, 2008 at 8:57 AM, Jefferson Heard
wrote: I tried using liftM on writeFile, but it then complained that "newanns" was a string instead of a list of strings, which I don't understand at all.
liftM isn't what you think it is.
liftM :: (a -> b) -> (m a -> m b) which is doing something weird depending how you inserted it: liftM (writeFile "x") :: Monad m => m String -> m (IO ()) which could theoretically have m get forced to be a list as the typechecker tries to figure out how to decipher this mess... liftM (writeFile "x") :: [String] -> [IO ()] or something else weird.
Probably: writeFile :: FilePath -> String -> IO () liftM writeFile :: Monad m => m FilePath -> m (String -> IO ()) liftM writeFile "path" Will unify "path"::[Char] with m Filepath. Instantiate m to [] (by head matching), but [Char] does not match [Filepath] (= [String]), giving the error the OP mentioned.
participants (4)
-
allan
-
Jefferson Heard
-
Luke Palmer
-
Ryan Ingram