
[Now with 100% more correct darcs get URLs.] I'm currently getting Paolo Martini's Google Summer of Code project, an updated version of Parsec, into a releasable state, and I will be maintaining it for at least a while. Paolo's major additions are: * The Parser monad has been generalized into a Parser monad transformer * The parsers have been generalized to work over a stream of any type, in particular, with bytestrings. I have made a few minor additions as well: * There is Haddock documentation for almost all functions * The Parser monad now has Applicative/Alternative instances Currently, I am looking for people to give it a go reporting any bugs in the library or documentation, troubles building it, or changes/features they would like. I'm also interested in performance information. Most old Parsec code should be relatively easy but not trivial to port. There is a darcs repository on code.haskell.org. If nothing comes up, I'll put a package on Hackage in about a week or so. To get the code: darcs get http://code.haskell.org/parsec3 To build it, the standard cabal commands should work: http://haskell.org/haskellwiki/Cabal/How_to_install_a_Cabal_package Alternatively, you can use the cabal-install application: http://hackage.haskell.org/trac/hackage/wiki/CabalInstall The documentation can be generated also via the normal cabal routine, or via cabal-install. The Text.Parsec modules should be preferred to the Text.ParserCombinators.Parsec modules.

I'm not a fan of parameterizing the "Stream" class over the monad parameter `m':
class Stream s m t | s -> t where uncons :: s -> m (Maybe (t,s))
which leads to instance declarations like so:
instance Monad m => Stream [tok] m tok where uncons [] = return $ Nothing uncons (t:ts) = return $ Just (t,ts)
I looked through the sources and I didn't see anywhere where this
parameterization gained anything. As a proof of this I did a
mechanical re-write removing the class parameter, and the library
still seems to work.
-Antoine
On Feb 1, 2008 11:15 PM, Derek Elkins
[Now with 100% more correct darcs get URLs.]
I'm currently getting Paolo Martini's Google Summer of Code project, an updated version of Parsec, into a releasable state, and I will be maintaining it for at least a while.
Paolo's major additions are: * The Parser monad has been generalized into a Parser monad transformer * The parsers have been generalized to work over a stream of any type, in particular, with bytestrings.
I have made a few minor additions as well: * There is Haddock documentation for almost all functions * The Parser monad now has Applicative/Alternative instances
Currently, I am looking for people to give it a go reporting any bugs in the library or documentation, troubles building it, or changes/features they would like. I'm also interested in performance information.
Most old Parsec code should be relatively easy but not trivial to port. There is a darcs repository on code.haskell.org. If nothing comes up, I'll put a package on Hackage in about a week or so.
To get the code: darcs get http://code.haskell.org/parsec3
To build it, the standard cabal commands should work: http://haskell.org/haskellwiki/Cabal/How_to_install_a_Cabal_package
Alternatively, you can use the cabal-install application: http://hackage.haskell.org/trac/hackage/wiki/CabalInstall
The documentation can be generated also via the normal cabal routine, or via cabal-install.
The Text.Parsec modules should be preferred to the Text.ParserCombinators.Parsec modules.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, 2 Feb 2008, Antoine Latter wrote:
I'm not a fan of parameterizing the "Stream" class over the monad parameter `m': <snip> I looked through the sources and I didn't see anywhere where this parameterization gained anything. As a proof of this I did a mechanical re-write removing the class parameter, and the library still seems to work.
AngloHaskell attendees may remember the quickie I did on handling the layout rule via a parsing monad transformer - removing this would stop me from generating the input stream in a particular monad and break the trick behind it. The idea was to use a lexing monad which the parser would be stacked on top of, such that the parser could communicate with the lexer and delayout function. Then when the parser failed at a point where a closing brace would allow parsing to continue, it could backtrack in the stream, tell the lexer that it failed the first time and ask for the character again - and if the layout rule allows it at that point, the returned character would this time be a closing brace. -- flippa@flippac.org Performance anxiety leads to premature optimisation

On Feb 2, 2008 5:28 PM, Antoine Latter
I'm not a fan of parameterizing the "Stream" class over the monad parameter `m':
class Stream s m t | s -> t where uncons :: s -> m (Maybe (t,s))
which leads to instance declarations like so:
instance Monad m => Stream [tok] m tok where uncons [] = return $ Nothing uncons (t:ts) = return $ Just (t,ts)
To expand on this point, side-effect instances of Stream don't play nice with the backtracking in Text.Parsec.Prim.try:
import Text.Parsec import Text.Parsec.Prim import System.IO import Control.Monad
type Parser a = (Stream s m Char) => ParsecT s u m a
This particular instance was suggested by Derek.
instance Stream Handle IO Char where uncons hdl = do b <- hIsEOF hdl if b then return Nothing else liftM (\c -> Just (c,hdl)) getChar
testParser :: Parser String testParser = try (string "hello1") <|> string "hello2"
test1 = runPT testParser () "stdin" stdin >>= print test2 = hGetLine stdin >>= print . runP testParser () "stdin"
"test1" uses the (Stream Handle IO Char) instance, "test2" uses the (Monad m => Stream [a] m a) instance. For input "hello2", test2 produces a valid parse while test1 does not. -Antoine

On Sat, 2008-02-02 at 20:43 -0600, Antoine Latter wrote:
On Feb 2, 2008 5:28 PM, Antoine Latter
wrote: I'm not a fan of parameterizing the "Stream" class over the monad parameter `m':
class Stream s m t | s -> t where uncons :: s -> m (Maybe (t,s))
which leads to instance declarations like so:
instance Monad m => Stream [tok] m tok where uncons [] = return $ Nothing uncons (t:ts) = return $ Just (t,ts)
To expand on this point, side-effect instances of Stream don't play nice with the backtracking in Text.Parsec.Prim.try:
import Text.Parsec import Text.Parsec.Prim import System.IO import Control.Monad
type Parser a = (Stream s m Char) => ParsecT s u m a
This particular instance was suggested by Derek.
instance Stream Handle IO Char where uncons hdl = do b <- hIsEOF hdl if b then return Nothing else liftM (\c -> Just (c,hdl)) getChar
testParser :: Parser String testParser = try (string "hello1") <|> string "hello2"
test1 = runPT testParser () "stdin" stdin >>= print test2 = hGetLine stdin >>= print . runP testParser () "stdin"
"test1" uses the (Stream Handle IO Char) instance, "test2" uses the (Monad m => Stream [a] m a) instance.
For input "hello2", test2 produces a valid parse while test1 does not.
Note that instance has a typo in it (which I fixed before testing this myself): getChar should be (hGetChar hdl) (though that makes no difference when you pass in stdin)

On Sat, 2 Feb 2008, Antoine Latter wrote:
To expand on this point, side-effect instances of Stream don't play nice with the backtracking in Text.Parsec.Prim.try:
import Text.Parsec import Text.Parsec.Prim import System.IO import Control.Monad
type Parser a = (Stream s m Char) => ParsecT s u m a
This particular instance was suggested by Derek.
<snip> We've been kicking this around on IRC a little, it took me a moment to remember the problem. Basically the problem isn't parsec/try playing badly with the stream - it's the stream playing badly with parsec/try. You need to keep track of where in the file you are and either cache it in an IORef or use seek to jump about appropriately. At the moment, Derek's instance doesn't know where it is in the stream so Parsec's backtracking is invisible to the underlying monad. That caching is the source of the potential leak I mentioned to you, because Parsec doesn't currently tell the stream when it's committed up to a given point and anything preceding it can be dropped safely. We'll tell the list a nice story about this over the coming week. For now, it's nearly 3am here and I should get to bed! -- flippa@flippac.org The task of the academic is not to scale great intellectual mountains, but to flatten them.

Another picky nit: The monad transformer type is defined as such:
data ParsecT s u m a = ParsecT { runParsecT :: State s u -> m (Consumed (m (Reply s u a))) }
with the Consumed and reply types as:
data Consumed a = Consumed a | Empty !a
data Reply s u a = Ok !a !(State s u) ParseError | Error ParseError
What's the advantage of having a double-wrapping of the base monad `m' over the simpler type: data ParsecT s u m a = ParsecT { runParsecT :: State s u -> m (Consumed (Reply s u a)) } -Antoine

On Sun, 3 Feb 2008, Antoine Latter wrote:
Another picky nit:
The monad transformer type is defined as such:
data ParsecT s u m a = ParsecT { runParsecT :: State s u -> m (Consumed (m (Reply s u a))) }
with the Consumed and reply types as:
data Consumed a = Consumed a | Empty !a
data Reply s u a = Ok !a !(State s u) ParseError | Error ParseError
What's the advantage of having a double-wrapping of the base monad `m' over the simpler type:
data ParsecT s u m a = ParsecT { runParsecT :: State s u -> m (Consumed (Reply s u a)) }
It's a necessary part of how Parsec works - both the Consumed and the Reply depend on the input stream, which is now generated from within the base monad. The Consumed result is evaluated in advance of the Reply, so keeping the computations separate preserves an important piece of laziness as m could be a strict monad. For now it's probably a good idea to look for issues that're visible to client code? Turning Parsec into a transformer was long considered an invitation to serious confusion, so it's not surprising that a few things look odd and a few others can be generalised in ways that aren't immediately obvious. -- flippa@flippac.org "The reason for this is simple yet profound. Equations of the form x = x are completely useless. All interesting equations are of the form x = y." -- John C. Baez

On Feb 4, 2008 9:11 PM, Philippa Cowderoy
It's a necessary part of how Parsec works - both the Consumed and the Reply depend on the input stream, which is now generated from within the base monad. The Consumed result is evaluated in advance of the Reply, so keeping the computations separate preserves an important piece of laziness as m could be a strict monad.
For now it's probably a good idea to look for issues that're visible to client code? Turning Parsec into a transformer was long considered an invitation to serious confusion, so it's not surprising that a few things look odd and a few others can be generalised in ways that aren't immediately obvious.
After I determined that the pre-release worked fine for the biggest set of parsers I have, I had to find other things to bring up :-) -Antoine

Probably a weird idea but could this be useful?
class (Monad m) => Stream s m t | s -> t where
uncons :: s -> m (m (t,s))
for example:
instance (Monad m) => Stream [t] m t where
uncons [] = return $ fail "uncons []"
uncons (t:ts) = return $ return (t,ts)
One small advantage is that Streams can have custom error messages
when there's no input.
Also, using 'uncons' could be as simple as: 'join . uncons'.
Bas
On Feb 2, 2008 6:15 AM, Derek Elkins
[Now with 100% more correct darcs get URLs.]
I'm currently getting Paolo Martini's Google Summer of Code project, an updated version of Parsec, into a releasable state, and I will be maintaining it for at least a while.
Paolo's major additions are: * The Parser monad has been generalized into a Parser monad transformer * The parsers have been generalized to work over a stream of any type, in particular, with bytestrings.
I have made a few minor additions as well: * There is Haddock documentation for almost all functions * The Parser monad now has Applicative/Alternative instances
Currently, I am looking for people to give it a go reporting any bugs in the library or documentation, troubles building it, or changes/features they would like. I'm also interested in performance information.
Most old Parsec code should be relatively easy but not trivial to port. There is a darcs repository on code.haskell.org. If nothing comes up, I'll put a package on Hackage in about a week or so.
To get the code: darcs get http://code.haskell.org/parsec3
To build it, the standard cabal commands should work: http://haskell.org/haskellwiki/Cabal/How_to_install_a_Cabal_package
Alternatively, you can use the cabal-install application: http://hackage.haskell.org/trac/hackage/wiki/CabalInstall
The documentation can be generated also via the normal cabal routine, or via cabal-install.
The Text.Parsec modules should be preferred to the Text.ParserCombinators.Parsec modules.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Is it good or bad to add: instance (MonadIO m) => MonadIO (ParsecT s u m)

On Thu, 7 Feb 2008, Albert Y. C. Lai wrote:
Is it good or bad to add:
instance (MonadIO m) => MonadIO (ParsecT s u m)
I don't see any reason not to add it - it's not as if we can prevent people lifting to IO! Good catch. -- flippa@flippac.org A problem that's all in your head is still a problem. Brain damage is but one form of mind damage.
participants (5)
-
Albert Y. C. Lai
-
Antoine Latter
-
Bas van Dijk
-
Derek Elkins
-
Philippa Cowderoy