[Haskell-cafe] Badly designed Parsec combinators?

Udo Stenzel u.stenzel at web.de
Thu Feb 16 10:09:03 EST 2006


Juan Carlos Arevalo Baeza wrote:
> myParser :: Parser ()
> myParser =
>        do  string "Hello"
>            optional (string ", world!")
> 
>   It makes no sense for myParser to generate any values, especially not 
> the result from the optional statement, so it is set to return ().

Don't you think this will interfere somehow with type inference?  I
wouldn't like a function that might decide to throw away its result if
(erroneously) used in a context that wouldn't need it.  I also think
almost every function has a sensible result, and written with the right
combinator, can return it without too much hassle.  So I'd probably
write:

yourParser :: Parser String
yourParser = liftM2 (++) (string "Hello")
                         (option "" (string ", world!")

I also find it very convenient to have a combinator that does a bind and
return the unmodified result of the first computation.  With that you
get:

(*>) :: Monad m => m a -> m b -> m a
m *> n = do a <- m ; n ; return a

ourParser :: Parser String
ourParser = string "Hello" *> optional (string ", world!")


Therefore, implicit (return ()) is selsdom useful, has the potential to
cause annoying silent failures and is generally not worth the hassle.


>   Another case where I encounter this is with the "when" function:
> 
> myParser2 :: Bool -> Parser ()
> myParser2 all =
>        do  string "Hello"
>            when all $
>                do  string ", world"
>            string "!"

A better fix would be more flexible when:

when :: Monad m => Bool -> m a -> m (Maybe a)
when True  m = Just `liftM` m
when False _ = return Nothing

...which is quite similar to the proposed change to Parsec's 'optional'.
I'd support both.

 
> It resembles a lot the 
> automatic conversions that C++ does.

I'm more reminded of Perl...


Udo.
-- 
Avoid strange women and temporary variables.
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://www.haskell.org//pipermail/haskell-cafe/attachments/20060216/5760b596/attachment.bin


More information about the Haskell-Cafe mailing list