[Haskell-beginners] Re: Simplifying code

edgar klerks edgar.klerks at gmail.com
Tue Feb 9 23:49:46 EST 2010


Hello all,

I have a very interesting alternative solution of the problem. First I
generate a tree with all the permutations:

eg if I want to find al permutations of ao, I get the following tree

   [a   @]
    |     |
  [o 0] [o 0]

Then I walk trough the tree so I can print it. There is only one ugly thing.
Showtree' returns a string (in our example aoa0 at o@0). To make it a list i
put a \n between a left and right node and then use lines to make it a list
of strings. Can someone point me in the right direction how to beautify it a
bit?

I also have an annoying problem with gmail and firefox. It seems it doesn
add my posts to the current thread, but starts a new one. Oh well think I
switch to evolution. I will review all yours solutions tomorrow. I saw some
very beautifull things.

With kind regards,

Edgar Klerks

module Main where
import Data.Char

data WordTree = Chain (Char,WordTree)
        |   Choice (Char, WordTree) (Char, WordTree)
        |   Stop

instance Show WordTree where
        show = unlines.showTree

type Rule = (Char, Char)
type Rules = [Rule]

infixl 4 ==>

a ==> b = (a,b)

rules :: Rules
rules = [ 'a' ==> '@', 'l' ==> '|']


buildTree :: String -> Rules -> WordTree
buildTree [] r = Stop
buildTree (c:cs) r = case lookup c r of
                        Just a -> Choice (a, buildTree cs r) (c, buildTree
cs r)
                        Nothing -> Chain (c, buildTree cs r)


showTree a = lines $ showTree' a []

showTree' (Chain (a,b)) p  = a : showTree' b p
showTree' (Choice (a,b) (c,d)) p  = c : showTree' d p ++ "\n" ++ (a :
showTree' b p)
showTree' (Stop) p   = p
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20100209/175b9dd9/attachment.html


More information about the Beginners mailing list