
I've been struggling with writing a parser that needs to parse include files within source files. So far I cannot get this to work (in reality to get work done I wrote a kludge that returns a list of include filenames to be run later in a pure IO function. I realized that this just amounted to creating my own half-assed monad system so I really don't want to use this approach). I have read the tutorials I could find on monad transformers but I still don't see what's going on. I'm using the Parsec parser library. Here's an simple example of what I've tried. I also tried using liftIO and got a message about needing to add an instance of MonadIO. This made more sense but the type of liftIO is baffling class Monad m => MonadIO m where liftIO :: IO a -> m a But how do you define this function? There is no constructor for "IO a" that you can "take apart". Anyway, here is the code that just uses lift. Keep in mind that the outer monad is just "GenParser Char st [Char]". I'm guessing this is wrong and I should have a transformer monad as the outer layer. But which one? and how to use it? pio = do { s <- many1 alphaNum; input <- lift (readFile s); return input; } go6 = runParser pio () "" "This is a test" ================================= ghc output from trying to load this is ================================= Couldn't match kind `* -> * -> *' against `(* -> *) -> * -> *' When matching the kinds of `GenParser Char :: * -> * -> *' and `t :: (* -> *) -> * -> *' Expected type: GenParser Char st Inferred type: t IO In a 'do' expression: lift (writeFile "Foo" s) ____________________________________________________________________________________ Fussy? Opinionated? Impossible to please? Perfect. Join Yahoo!'s user panel and lay it on us. http://surveylink.yahoo.com/gmrs/yahoo_panel_invite.asp?a=7

Gregory Propf wrote:
I've been struggling with writing a parser that needs to parse include files within source files. So far I cannot get this to work (in reality to get work done I wrote a kludge that returns a list of include filenames to be run later in a pure IO function. I realized that this just amounted to creating my own half-assed monad system so I really don't want to use this approach). I have read the tutorials I could find on monad transformers but I still don't see what's going on. I'm using the Parsec parser library. Here's an simple example of what I've tried. I also tried using liftIO and got a message about needing to add an instance of MonadIO. This made more sense but the type of liftIO is baffling
The fun part is that Parsec already has a feature for include files... (I can't remember where the heck it is or how you use it though.)

Gregory Propf, Sat, 11 Aug 2007 13:06:43 -0700:
but the type of liftIO is baffling
class Monad m => MonadIO m where liftIO :: IO a -> m a
But how do you define this function? There is no constructor for "IO a" that you can "take apart".
If not using unsafePerformIO, which is usually not what we want, the monad m in question must incorporate IO. That is, it could be defined something like (say we want a parser with state): newtype IOParser tok s a = IOParser (s -> [tok] -> IO (s,a)) You can then define liftIO without “taking apart” the IO value; instead you put liftIO's IO action (IO a) into IOParser's IO action (IO (s,a)). Parsec does not define any such parser, though, so there's nothing for which you may define an instance of MonadIO. Malte

Malte Milatz wrote:
If not using unsafePerformIO, which is usually not what we want, the monad m in question must incorporate IO. That is, it could be defined something like (say we want a parser with state):
newtype IOParser tok s a = IOParser (s -> [tok] -> IO (s,a))
You can then define liftIO without “taking apart” the IO value; instead you put liftIO's IO action (IO a) into IOParser's IO action (IO (s,a)). Parsec does not define any such parser, though, so there's nothing for which you may define an instance of MonadIO.
Malte
I'm making (or have "made") such a thing, although not necessarily atop IO, atop any monad that provides certain stream-like functionality. It's kind of done, but not really. $ darcs get http://samuelhughes.com/darcs/partran/ That is virtually completely untested and has not been proven correct either. Also, whatever documentation there is has probably accidentally been copied and pasted from Parsec's (except for the documentation of Stream.hs). Some of the unthinkingly done translations of the files found in Parsec's hierarchy seem to be idiomatically immoral. (Token.hs comes to mind. Something went wrong with functional dependencies and avoiding things like breaking the coverage condition/undecidable instances and it hurts. Maybe somebody could tell me what I'm doing wrong.) Also, some functions and definitions of things might be appropriately moved around, and you'll probably end up having to import more than you'd like to. "Text.ParserCombinators.ParTran.Parsec" /might/ currently contain a correct simulation of "Text.ParserCombinators.Parsec". - Sam
participants (4)
-
Andrew Coppin
-
Gregory Propf
-
Malte Milatz
-
Sam Hughes