[Haskell-cafe] Problem compiling a CGI script that needs to write to file during its execution

Jefferson Heard jefferson.r.heard at gmail.com
Tue Jul 29 11:57:13 EDT 2008


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


More information about the Haskell-Cafe mailing list