[Haskell-cafe] I want my free (and good looking) parser!
Slavomir Kaslev
slavomir.kaslev at gmail.com
Mon Oct 6 11:38:58 EDT 2008
I am writing a Parsec parser for a C-like language and I have several datas that
look more or less like this one:
> import Control.Monad( liftM )
> import Text.ParserCombinators.Parsec
> data FooBar = Foo | Bar
> deriving (Show,Read,Bounded,Enum)
Looking at these, it seems that there should be no need to write a parser for
this guy by hand. We already know that it is bounded and enumerable, so we can
get a list of all possible FooBars:
> enumAll :: (Bounded a, Enum a) => [a]
> enumAll = enumFromTo minBound maxBound
Also, we know how to show and read each FooBar. Therefore, I should get a free
parser!
> freeParser :: (Enum a, Bounded a, Show a, Read a) => Parser a
Here is one use of freeParser:
> paramMod = option Foo freeParser
> test = parseTest $ do { x <- paramMod; eof; return x }
Not suprisingly:
test "Foo" => Foo
test "Bar" => Bar
test "" => Foo
I had a little hard time figuring out how this parser should look. The best I
came up with was:
> 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))
[Actually, in my code I use reserved' (reserved' x = reserved x >> return x)
instead of string, where reserved is from Parsec's builtin tokenizer (which does
some neat things behind the curtains). Here string is used just to
illustrate the
expamle.]
The problem is that freeParser, although useful, is far from elegant. It's
something that I came up with by trial and error. In short: it's a hack.
I would like to hear your suggestions about how it can be beautified.
Thank you in advance.
Cheers!
--
Slavomir Kaslev
More information about the Haskell-Cafe
mailing list