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 
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to