Haskell Quiz/Morse Code/Solution Dolio

From HaskellWiki
< Haskell Quiz‎ | Morse Code
Revision as of 06:11, 22 April 2007 by Dolio (talk | contribs) (creation)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.


This solution uses a naive implementation of monadic parser combinators, simply using the state transform of the list monad. For more information on how all this works, a google search for 'monadic parser combinators' should be more than sufficient.

import Data.List
import Control.Monad
import Control.Monad.State

-- The classic parser monad, with input token type a, and output type b
type Parser a b = StateT [a] [] b

morse = [ ".-", "-...", "-.-.", "-..", ".", "..-.", "--.", "....", "..", ".---"
        , "-.-", ".-..", "--", "-.", "---", ".--.", "--.-", ".-.", "...", "-"
        , "..-", "...-", ".--", "-..-", "-.--", "--.." ]

token :: Parser a a
token = do (a:as) <- get ; put as ; return a

satisfy :: (a -> Bool) -> Parser a ()
satisfy p = token >>= guard . p

many :: Parser a a -> Parser a [a]
many p = many1 p `mplus` return []

many1 :: Parser a a -> Parser a [a]
many1 p = liftM2 (:) p (many p)

total :: Parser a b -> Parser a b
total p = p >>= \b -> get >>= guard . null >> return b

string :: String -> Parser Char ()
string [] = return ()
string (x:xs) = satisfy (==x) >> string xs

morseLetter :: Parser Char Char
morseLetter = msum $ zipWith (\c l -> string c >> return l) morse ['a'..'z']

main = interact $ unlines . concatMap (evalStateT (total $ many morseLetter)) . words