[Haskell-cafe] Re: I want my free (and good looking) parser!

Jeremy Shaw jeremy at n-heptane.com
Mon Oct 6 14:13:30 EDT 2008


At Mon, 6 Oct 2008 20:20:57 +0300,
Slavomir Kaslev wrote:
> 
> On Mon, Oct 6, 2008 at 8:07 PM, Christian Maeder
> <Christian.Maeder at dfki.de> wrote:
> > Slavomir Kaslev wrote:
> >>> freeParser = freeParser' minBound
> >>>     where enumAll' :: (Bounded a, Enum a) => a -> [a]
> >>>           enumAll' _ = enumAll
> >>>           freeParser' :: (Enum a, Bounded a, Show a, Read a) => a -> Parser a
> >>>           freeParser' x = liftM read $ choice (map (string . show) (enumAll' x))
> >
> > 1. I would use an explicit function argument instead of "Show" to allow
> > strings starting with lower case.
> >
> 
> You are right. But that was not the problem. The problem was that I
> wrestled with Haskell's type system quite a bit to make freeParser
> work. What I want to write is
> 
> freeParser :: (Enum a, Bounded a, Show a, Read a) => Parser a
> freeParser = liftM read $ choice (map (string . show) enumAll)
> 
> but it doesn't compile. How can I make this piece code work?

I would start by adding this to the top of the file:

> {-# LANGUAGE ScopedTypeVariables, FlexibleContexts  #-}

Then add 'forall a.' to the type signature of freeParser. This causes
freeParser' and freeParser to have the same value for 'a'. 

Now you can add an explicit type signature to (enumAll :: [a])

> freeParser :: forall a. (Enum a, Bounded a, Show a, Read a) => Parser a
> freeParser = freeParser' minBound
>     where freeParser' :: (Enum a, Bounded a, Show a, Read a) => a -> Parser a
>           freeParser' x = liftM read $ choice (map (string . show) (enumAll :: [a]))

The reseason you have to explicitly type enumAll is because you do a
show and then a read. Looking at a simplified case, we can see that
the types in this expression are ambigious:

 read (show 1.0)

show :: (Show a) => a -> String
read :: (Read a) => String -> a

It is perfectly valid typewise to do,:

 read (show 1.0) :: Char

Of course, that will result in a runtime error:

*Main> read (show 1.0) :: Char
*** Exception: Prelude.read: no parse

If we rewrite freeParser like this, then we don't need any special extensions:

> freeParser :: (Enum a, Bounded a, Show a, Read a) => Parser a
> freeParser = freeParser' minBound
>     where freeParser' :: (Enum a, Bounded a, Show a, Read a) => a -> Parser a
>           freeParser' x = choice (map (\x -> string (show x) >> return x) enumAll)

Some might consider this prettier:

> freeParser :: (Enum a, Bounded a, Show a, Read a) => Parser a
> freeParser = freeParser' minBound
>     where freeParser' :: (Enum a, Bounded a, Show a, Read a) => a -> Parser a
>           freeParser' x = choice [ string (show x) >> return x | x <- enumAll ]

Anyway, there is another problem -- if you extend you datatype with a
constructor Foomatic:

> data FooBar = Foo | Foomatic | Bar
>             deriving (Show,Read,Bounded,Enum)

you get the error:

test "Foomatic"
parse error at (line 1, column 4):
unexpected "m"
expecting end of input

This is because the parser wil successfully parse Foo and so it won't
even try parsing foomatic.

As a cheap hack we can do this:

> freeParser :: (Ord a, Enum a, Bounded a, Show a, Read a) => Parser a
> freeParser = freeParser' minBound
>     where freeParser' :: (Ord a, Enum a, Bounded a, Show a, Read a) => a -> Parser a
>           freeParser' x = choice [ try (string (show x)) >> return x | x <- reverse $ sort enumAll ]

We sort the constructors by reverse alphabetical order so that the
parser will try Foomatic before trying Foo. We also need to use the
'try' function so that if Foomatic fails it will still try Foo.

This is not a particularily efficient fix though.

j.


More information about the Haskell-Cafe mailing list