[Haskell-cafe] Parsec beginners problem
Chris Kuklewicz
haskell at list.mightyreason.com
Sat Apr 28 08:45:51 EDT 2007
Jim Burton wrote:
> You could be right about delimiters, but handling the ambiguous instances is
> the challenge in this case, which is a Ruby Quiz
> [http://www.rubyquiz.com/quiz121.html] - I thought it would be a good use
> for Parsec, and the user guide talks about try..<|> as the tool for it, as
> in
>
> testOr2 = try (string "(a)")
> <|> string "(b)"
>
There are other modules that come with Haskell than
Text.ParserCombinators.Parsec
such as
Text.ParserCombinators.ReadP
The solution with ReadP makes for a very short 'parse' function. Note that
reader is built in a recursive manner.
> module Morse where
>
> import Control.Monad(guard)
> import Text.ParserCombinators.ReadP
>
> parse = map fst . readP_to_S reader
> where reader = done <++ choice (map pairToReader table)
> done = look >>= guard . null >> return []
> pairToReader (s,c) = string s >> fmap (c:) reader
>
> table = (".-",'A'):
> ("-...",'B'):
> ("-.-.",'C'):
> ("-..",'D'):
> (".",'E'):
> ("..-.",'F'):
> ("--.",'G'):
> ("....",'H'):
> ("..",'I'):
> (".---",'J'):
> ("-.-",'K'):
> (".-..",'L'):
> ("--",'M'):
> ("-.",'N'):
> ("---",'O'):
> (".--.",'P'):
> ("--.-",'Q'):
> (".-.",'R'):
> ("...",'S'):
> ("-",'T'):
> ("..-",'U'):
> ("...-",'V'):
> (".--",'W'):
> ("-..-",'X'):
> ("-.--",'Y'):
> ("--..",'Z'):
> []
The table is sorted which means the result of 'parse' is in sorted alphabetical
order.
It also does not check which are dictionary words, so it finds many solutions:
*Morse> length $ parse "...---..-....-"
5104
*Morse> take 10 $ parse "...---..-....-"
["EEAGAEEEA","EEAGAEEEET","EEAGAEEIT","EEAGAEEU","EEAGAEIA","EEAGAEIET","EEAGAEST","EEAGAEV","EEAGAHT","EEAGAIEA"]
--
Chris
More information about the Haskell-Cafe
mailing list