
Am Mittwoch 10 Februar 2010 05:49:46 schrieb edgar klerks:
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@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
Apparently, it doesn't set the in-reply-to field. That should be configurable. things.
With kind regards,
Edgar Klerks
module Main where import Data.Char
data WordTree = Chain (Char,WordTree)
Why add the extra tuple? Better: Chain Char WordTree
| Choice (Char, WordTree) (Char, WordTree)
Again, the tuples aren't necessary.
| Stop
instance Show WordTree where show = unlines.showTree
type Rule = (Char, Char)
I think it would be better to have type Rule = (Char,[Char]) or even data Rule a = Sub a [a] or use a Map a [a]. You gain more flexibility that way and can use the same code if you can replace a Char (or whatever) with one of any number of possibilities. The WordTree type would then become data WordTree = Branch [(Char, WordTree)] | Tip type Rules = Map Char [Char] rules :: Rules rules = fromList [('a',['a','@']),('l',['l','|'])] subs :: Char -> Rules -> [Char] subs c rs = findWithDefault [c] c rs buildTree :: String -> Rules -> WordTree buildTree (c:cs) rs = let st = buildTree cs rs in Branch [(s,st) | s <- subs c rs] buildTree "" _ = Tip showTree (Branch ts) = [c:xs | (c,st) <- ts, xs <- showTree st] showTree Tip = [""]
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)
Share the subtree, Just a -> let st = buildTree cs r in Choice (a,st) (c,st)
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
showTree :: WordTree -> [String] showTree (Chain (a,b)) = [a:xs | xs <- showTree b] showTree (Choice (a,b) (c,d)) = [a:xs | xs <- showTree b] ++ [c:ys | ys <- showTree d] showTree Stop = [""]