
This is probably an easy question, but I'm having a problem with parsec in the IO monad. The essential parts of my program looks like this...
import Text.ParserCombinators.Parsec
main = do input <- getContents putStr $ show $ parse_text shape_parse input --(cam, sh) <- parse_text shape_parse input --putStr $ (show cam) ++ "\n" ++ (show sh) putStr "\n"
parse_text p input = case (parse p input) of Left err -> error $ "Invalid input"++(show err) Right x -> x
shape_parse = do cam <- camera_parse shapes <- many1 (sphere_parse <|> plane_parse) return (cam, shapes)
-- blah, blah, blah, etc.
This works fine in GHC. The types for parse_text and shape_parse are... *Main> :t parse_text parse_text :: forall a tok. GenParser tok () a -> [tok] -> a *Main> :t shape_parse shape_parse :: forall st. GenParser Char st (Camera, [Shape]) *Main> Now when I change main to...
main = do input <- getContents --putStr $ show $ parse_text shape_parse input (cam, sh) <- parse_text shape_parse input putStr $ (show cam) ++ "\n" ++ (show sh) putStr "\n"
I get the following message from GHCi... p2.hs:38: Couldn't match `IO t' against `(Camera, [Shape])' Expected type: GenParser Char () (IO t) Inferred type: GenParser Char () (Camera, [Shape]) In the first argument of `parse_text', namely `shape_parse' In a 'do' expression: (cam, sh) <- parse_text shape_parse input I'm probably missing something silly. Any hint would be appreciated. Thanks, Greg Buchholz