
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 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

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 = [""]

He Daniel, I use the Data.Map now, this makes it way more flexibler data WordTree
= Branch [(Char, WordTree)] | Tip
I only don't use this type of Tree. I am not sure how it works, but it looks good, so I will experiment with it. Is it a so called rose tree? (Then I can find some articles about it).
Share the subtree, Just a -> let st = buildTree cs r in Choice (a,st) (c,st)
Stupid thing not to do, think I overlooked it :)
Thanks again. Edgar

He Daniel,
I used your showTree function because it works better than mine. I also
think the program is now truly functional. I will try to implement the other
tree on my own to see how it goes.
It now looks like this:
module Main where
import Data.Char
import System
import qualified Data.Map as M
import Control.Applicative ((<$>))
--- CONFIG SECTION ---
-- add the characters you want to permutate here--
rules :: Rules
rules = M.fromList [
'a' ==> "@",
'l' ==> "|",
'w' ==> "\\|/",
'v' ==> "\\/",
'o' ==> "0"]
data WordTree = Chain String WordTree
| Choice String WordTree String WordTree
| Stop
deriving Show
--instance Show WordTree where
-- show = unlines.showTree
type Rules = M.Map Char [Char]
infixl 4 ==>
(==>) :: a -> b -> (a, b)
a ==> b = (a, b)
buildTree :: String -> Rules -> WordTree
buildTree [] r = Stop
buildTree (c:cs) r = case M.lookup c r of
Just a -> let p = buildTree cs r
in Choice a p [c] p
Nothing -> Chain [c] $ buildTree cs r
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 = [""]
main :: IO ()
main = do
filename <- head <$> getArgs
wordlist <- readFile $ filename
let a = (flip buildTree $ rules) <$> (lines wordlist) >>= showTree
mapM_ putStrLn a
~
On Wed, Feb 10, 2010 at 1:47 PM, edgar klerks
He Daniel,
I use the Data.Map now, this makes it way more flexibler
data WordTree
= Branch [(Char, WordTree)] | Tip
I only don't use this type of Tree. I am not sure how it works, but it looks good, so I will experiment with it. Is it a so called rose tree? (Then I can find some articles about it).
Share the subtree, Just a -> let st = buildTree cs r in Choice (a,st) (c,st)
Stupid thing not to do, think I overlooked it :)
Thanks again.
Edgar
-- Flatliner ICT Service, Email: Edgar.klerks@gmail.com, Tel: +31727851429 Fax: +31848363080 Skype: edgar.klerks Website: flatlinerict.nl Adres: Koelmalaan 258, 1813JD, Alkmaar Nederland

Why add the extra tuple? Better: Chain Char WordTree
It feels a bit too loose. Think it is a imperative quirk. I remove the tupples. And I am going to change the type Rule to a Map. I have used that package before and it is fast and easy to use. Another question. I have a book Real World Haskell, which is great, but I would like to read somewhat more indepth stuff. Can you recommend one? Thanks for your advice. With kind regards, Edgar I switched to evolution. Hopefully it will take the in reply to field.
participants (2)
-
Daniel Fischer
-
edgar klerks