[Haskell-cafe] Parsec beginners problem

Jim Burton jim at sdf-eu.org
Sat Apr 28 09:58:35 EDT 2007


Chris Kuklewicz wrote:

[snip]

> 
> 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"]
> 
Thanks Chris, that's a neat solution and an eye opener for me -- I need 
to investigate the Text package I think.


More information about the Haskell-Cafe mailing list