
Hi All, I wrote a program which permutates a list words with some rules. For example if I feed it a list like: banana waterloo vraag It gives back the list: banana b@nana ban@na b@n@na banan@ b@nan@ ban@n@ b@n@n@ waterloo wa+erloo water|oo waterl0o etc However I have the feeling I am doing things to complicated. I am still a beginner. Would someone like to help me simplify somethings. If you think this is inappropriate please state also. I am not offended then. I understand you are offering your spare time to help me. The first thing I don't get is this. I recognize some things could be rewritten with a bind operator (because of the concat $ fmap), but I am puzzled how: mutateWords :: [Char] -> [[Char]] mutateWords word = nub.concat $ fmap snd <$> fmap unzip <$> ( foldr(\x z -> let char = snd x nm = number word lst = fst x in (insertAt char nm <$> lst) : z ) [[]] $ mw word ) Here is the full code: import Data.List import System import System.IO import Control.Applicative ---CONFIG section leat = ['s' ==> '$', 't' ==> '+', 'l' ==> '|', 'o' ==> '0','e' ==> '3', 'a' ==> '@', 'v' ==> '^'] leata = fst.unzip $ leat leatb = snd.unzip $ leat -- Perl like assoc lists infixl 1 ==> a ==> b = (a, b) -- Flipped fmap sometimes nicer infixl 4 <$$> xs <$$> f = f <$> xs -- first I need to find the positions of the mutatable charachters. findPositions :: [Char] -> [[Int]] findPositions xs = take (length index) $ index <*> [xs] where index = elemIndices <$> leata -- And generate all subsequences findSubSeq :: [Char] -> [[[Int]]] findSubSeq = fmap subsequences <$> findPositions -- Only change elements which needs to be changed insertAt :: Char -> [(Int, Char)] -> [Int] -> [(Int,Char)] insertAt c xs ps = xs <$$> (\x -> if (fst x) `elem` ps then (fst x , c) else x ) -- Couples character to mutable positions mw word = (findSubSeq word) `zip` leatb number = zip [0..] mutateWords :: [Char] -> [[Char]] mutateWords word = nub.concat $ fmap snd <$> fmap unzip <$> ( foldr(\x z -> let char = snd x nm = number word lst = fst x in (insertAt char nm <$> lst) : z ) [[]] $ mw word ) generateAll :: [Char] -> [[Char]] generateAll word = g lea $ mutateWords word where g 0 words = words g n words = g (n - 1) (nub $ words >>= mutateWords ) lea = length leata main = do filename <- getArgs wordlist <- readFile $ filename !! 0 let a = (words wordlist) >>= generateAll mapM_ putStrLn a -- Flatliner ICT Service, Email: Edgar.klerks@gmail.com, Tel: +31727851429 Fax: +31848363080 Skype: edgar.klerks Website: flatlinerict.nl Adres: Koelmalaan 258, 1813JD, Alkmaar Nederland

Hi,
I think that this is a case where you have to let the recursion do the
work for you.
Here is a solution, although it seems it generates the permutations in
a different order
than yours:
import Data.Maybe
leet = [('s', '$'), ('t', '+'), ('l', '|'), ('o', '0'), ('e', '3'),
('a', '@'), ('v', '^')]
mutateWords :: [String] -> [[String]]
mutateWords = map mutateWord
mutateWord :: String -> [String]
mutateWord [] = [[]]
mutateWord (c:cs) = concat . map perms $ mutateWord cs
where perms cs' = map (: cs') $ mutateLetter c
-- Returns a list of possible characters for c
mutateLetter :: Char -> [Char]
mutateLetter c = c : (maybeToList $ lookup c leet)
Basically, in mutateLetter you generate a list of possible letters.
For a char that
stays the same, we return [c]. For a char that has a substitution in
the leet list,
we return [c, c'].
Then in mutateWord we process the first letter, generate all the
choices and prepend
them to all the choices for the rest of the word.
Patrick
On Tue, Feb 9, 2010 at 3:11 PM, edgar klerks
Hi All,
I wrote a program which permutates a list words with some rules. For example if I feed it a list like:
banana waterloo vraag
It gives back the list:
banana b@nana ban@na b@n@na banan@ b@nan@ ban@n@ b@n@n@ waterloo wa+erloo water|oo waterl0o etc
However I have the feeling I am doing things to complicated. I am still a beginner. Would someone like to help me simplify somethings. If you think this is inappropriate please state also. I am not offended then. I understand you are offering your spare time to help me.
The first thing I don't get is this. I recognize some things could be rewritten with a bind operator (because of the concat $ fmap), but I am puzzled how:
mutateWords :: [Char] -> [[Char]] mutateWords word = nub.concat $ fmap snd <$> fmap unzip <$> ( foldr(\x z -> let char = snd x nm = number word lst = fst x in (insertAt char nm <$> lst) : z ) [[]] $ mw word )
Here is the full code:
import Data.List import System import System.IO import Control.Applicative
---CONFIG section
leat = ['s' ==> '$', 't' ==> '+', 'l' ==> '|', 'o' ==> '0','e' ==> '3', 'a' ==> '@', 'v' ==> '^']
leata = fst.unzip $ leat leatb = snd.unzip $ leat
-- Perl like assoc lists infixl 1 ==> a ==> b = (a, b)
-- Flipped fmap sometimes nicer infixl 4 <$$>
xs <$$> f = f <$> xs
-- first I need to find the positions of the mutatable charachters. findPositions :: [Char] -> [[Int]] findPositions xs = take (length index) $ index <*> [xs] where index = elemIndices <$> leata
-- And generate all subsequences findSubSeq :: [Char] -> [[[Int]]] findSubSeq = fmap subsequences <$> findPositions
-- Only change elements which needs to be changed insertAt :: Char -> [(Int, Char)] -> [Int] -> [(Int,Char)] insertAt c xs ps = xs <$$> (\x -> if (fst x) `elem` ps then (fst x , c) else x ) -- Couples character to mutable positions mw word = (findSubSeq word) `zip` leatb
number = zip [0..]
mutateWords :: [Char] -> [[Char]] mutateWords word = nub.concat $ fmap snd <$> fmap unzip <$> ( foldr(\x z -> let char = snd x nm = number word lst = fst x in (insertAt char nm <$> lst) : z ) [[]] $ mw word )
generateAll :: [Char] -> [[Char]] generateAll word = g lea $ mutateWords word where g 0 words = words g n words = g (n - 1) (nub $ words >>= mutateWords ) lea = length leata main = do filename <- getArgs wordlist <- readFile $ filename !! 0 let a = (words wordlist) >>= generateAll mapM_ putStrLn a
-- Flatliner ICT Service, Email: Edgar.klerks@gmail.com, Tel: +31727851429 Fax: +31848363080 Skype: edgar.klerks Website: flatlinerict.nl Adres: Koelmalaan 258, 1813JD, Alkmaar Nederland
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

Hi
A few remarks about your code:
1. 'String' is a type synonym for [Char]. It makes types like [[Char]]
more readable (at least for me).
2. There is something imperative in the way you code: I think you rely
too much on numbers as iterators. You don't have to use numbers to
drive the program control flow. Examples:
main = do
filename <- getArgs
wordlist <- readFile $ filename !! 0
Why not:
main = do
(filename:_) <- getArgs
wordlist <- readFile filename
Or:
main = do
filename <- head <$> getArgs
wordlist <- readFile filename
Another example:
generateAll :: String -> [String]
generateAll word = g lea $ mutateWords word
where g 0 words = words
g n words = g (n - 1) (nub $ words >>= mutateWords )
lea = length leata
The 'g' function can be rewritten to get rid of the index number.
Here is what I got:
-- https://mail.google.com/mail/#inbox/126b45c29341640f
import System.Environment ( getArgs )
import Control.Applicative ( (<$>) )
import Data.Set (Set)
import qualified Data.Set as Set
---CONFIG section
type Rule = (Char,Char)
infixl 1 ==>
a ==> b = (a, b)
rules :: [Rule]
rules = ['s' ==> '$',
't' ==> '+',
'l' ==> '|',
'o' ==> '0',
'e' ==> '3',
'a' ==> '@',
'v' ==> '^']
nubOrd :: (Ord a) => [a] -> [a]
nubOrd = Set.toList . Set.fromList
singleton x = [x]
-- CORE PART
-- we mutate all words, rule at a time. If we run out of rules, we finish.
mutateWords :: [Rule] -> String -> [String]
mutateWords rules word = foldr (\r acc -> nubOrd (concatMap (applyRule
r) acc)) (singleton word) rules
-- apply one rule to one word. the result is a list of words.
applyRule :: Rule -> String -> [String]
applyRule (old,new) wrd = aux wrd where
aux [] = [[]]
-- we may or may not apply our rule here.
aux (c:cs) | c == old = [ c':suf | suf <- aux cs, c' <- [old,new] ]
| otherwise = [ c :suf | suf <- aux cs ]
main = do
(filename:_) <- getArgs
wordlist <- words <$> readFile filename
let mutated = concatMap (mutateWords rules) wordlist
mapM_ putStrLn mutated
Best regards
Krzysztof Skrzętnicki
On Tue, Feb 9, 2010 at 21:11, edgar klerks
Hi All,
I wrote a program which permutates a list words with some rules. For example if I feed it a list like:
banana waterloo vraag
It gives back the list:
banana b@nana ban@na b@n@na banan@ b@nan@ ban@n@ b@n@n@ waterloo wa+erloo water|oo waterl0o etc
However I have the feeling I am doing things to complicated. I am still a beginner. Would someone like to help me simplify somethings. If you think this is inappropriate please state also. I am not offended then. I understand you are offering your spare time to help me.
The first thing I don't get is this. I recognize some things could be rewritten with a bind operator (because of the concat $ fmap), but I am puzzled how:
mutateWords :: [Char] -> [[Char]] mutateWords word = nub.concat $ fmap snd <$> fmap unzip <$> ( foldr(\x z -> let char = snd x nm = number word lst = fst x in (insertAt char nm <$> lst) : z ) [[]] $ mw word )
Here is the full code:
import Data.List import System import System.IO import Control.Applicative
---CONFIG section
leat = ['s' ==> '$', 't' ==> '+', 'l' ==> '|', 'o' ==> '0','e' ==> '3', 'a' ==> '@', 'v' ==> '^']
leata = fst.unzip $ leat leatb = snd.unzip $ leat
-- Perl like assoc lists infixl 1 ==> a ==> b = (a, b)
-- Flipped fmap sometimes nicer infixl 4 <$$>
xs <$$> f = f <$> xs
-- first I need to find the positions of the mutatable charachters. findPositions :: [Char] -> [[Int]] findPositions xs = take (length index) $ index <*> [xs] where index = elemIndices <$> leata
-- And generate all subsequences findSubSeq :: [Char] -> [[[Int]]] findSubSeq = fmap subsequences <$> findPositions
-- Only change elements which needs to be changed insertAt :: Char -> [(Int, Char)] -> [Int] -> [(Int,Char)] insertAt c xs ps = xs <$$> (\x -> if (fst x) `elem` ps then (fst x , c) else x ) -- Couples character to mutable positions mw word = (findSubSeq word) `zip` leatb
number = zip [0..]
mutateWords :: [Char] -> [[Char]] mutateWords word = nub.concat $ fmap snd <$> fmap unzip <$> ( foldr(\x z -> let char = snd x nm = number word lst = fst x in (insertAt char nm <$> lst) : z ) [[]] $ mw word )
generateAll :: [Char] -> [[Char]] generateAll word = g lea $ mutateWords word where g 0 words = words g n words = g (n - 1) (nub $ words >>= mutateWords ) lea = length leata main = do filename <- getArgs wordlist <- readFile $ filename !! 0 let a = (words wordlist) >>= generateAll mapM_ putStrLn a
-- Flatliner ICT Service, Email: Edgar.klerks@gmail.com, Tel: +31727851429 Fax: +31848363080 Skype: edgar.klerks Website: flatlinerict.nl Adres: Koelmalaan 258, 1813JD, Alkmaar Nederland
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Am Dienstag 09 Februar 2010 21:11:55 schrieb edgar klerks:
Hi All,
I wrote a program which permutates a list words with some rules. For example if I feed it a list like:
banana waterloo vraag
It gives back the list:
banana b@nana ban@na b@n@na banan@ b@nan@ ban@n@ b@n@n@ waterloo wa+erloo water|oo waterl0o etc
However I have the feeling I am doing things to complicated. I am still a beginner. Would someone like to help me simplify somethings.
Sure. If you don't mind that the mutations come in a different order, one thing that works wonders is "sequence", sequence :: Monad m => [m a] -> m [a] In particular, for m = [], sequence :: [[a]] -> [[a]]. Then, knowing what sequence does, we can write import Control.Monad (sequence) generateAll :: String -> [String] generateAll word = sequence (map f word) where f c = case lookup c leat of Just r -> [c,r] Nothing -> [c] For each letter in the word, we generate the list of all possible substitutions (map f), "woot" ~> [['w'],['o','0'],['o','0'],['t','+']] and then sequence them, choosing each combination of substitutions once. A little more efficient than sequence is generateAll :: String -> [String] generateAll word = allCombs (map f word) where f c = case lookup c leat of Just r -> [c,r] Nothing -> [c] allCombs :: [[a]] -> [[a]] allCombs (l:ls) = [h:t | t <- allCombs ls, h <- l] allCombs [] = [[]] -- sequence (l:ls) = [h:t | h <- l, t <- sequence ls] -- with the generators in reverse order, cf. -- http://www.haskell.org/pipermail/haskell-cafe/2009-December/070149.html
If you think this is inappropriate please state also.
How could it be? This list is for helping people understand Haskell better, exactly what you're after.
I am not offended then. I understand you are offering your spare time to help me.
If one thinks one's time isn't worth it, one can just ignore the post.
The first thing I don't get is this. I recognize some things could be rewritten with a bind operator (because of the concat $ fmap), but I am puzzled how:
mutateWords :: [Char] -> [[Char]] mutateWords word = nub.concat $ fmap snd <$> fmap unzip <$> ( foldr(\x z ->
let char = snd x nm = number word lst = fst x in (insertAt char nm <$> lst) : z ) [[]] $ mw word )
Here is the full code:
import Data.List import System import System.IO import Control.Applicative
---CONFIG section
leat = ['s' ==> '$', 't' ==> '+', 'l' ==> '|', 'o' ==> '0','e' ==> '3', 'a' ==> '@', 'v' ==> '^']
leata = fst.unzip $ leat
leata = map fst leat leatb = map snd leat
leatb = snd.unzip $ leat
-- Perl like assoc lists infixl 1 ==> a ==> b = (a, b)
-- Flipped fmap sometimes nicer infixl 4 <$$>
xs <$$> f = f <$> xs
-- first I need to find the positions of the mutatable charachters.
No, you don't need to do that, it's in general more efficient to not care about positions when dealing with lists.
findPositions :: [Char] -> [[Int]] findPositions xs = take (length index) $ index <*> [xs] where index = elemIndices <$> leata
[f1, ..., fm] <*> [x1, ..., xn] produces a list of length m*n, so length (index <*> [xs]) == length index * length [xs] == length index ~> remove "take (length index) $"
-- And generate all subsequences findSubSeq :: [Char] -> [[[Int]]] findSubSeq = fmap subsequences <$> findPositions
-- Only change elements which needs to be changed insertAt :: Char -> [(Int, Char)] -> [Int] -> [(Int,Char)] insertAt c xs ps = xs <$$> (\x -> if (fst x) `elem` ps then (fst x , c) else x ) -- Couples character to mutable positions mw word = (findSubSeq word) `zip` leatb
number = zip [0..]
mutateWords :: [Char] -> [[Char]] mutateWords word = nub.concat $ fmap snd <$> fmap unzip <$> ( foldr(\x z ->
let char = snd x nm = number word lst = fst x in (insertAt char nm <$> lst) : z ) [[]] $ mw word )
Okay, I give up, that's too complicated :) One general remark. When you have an Ord instance, "nub" is an extremely bad idea (unless your lists are really short), as it's quadratic in the length of the list. map head . group . sort or import Data.Set toList . fromList are much better [O(l * log l) where l = length xs]
generateAll :: [Char] -> [[Char]] generateAll word = g lea $ mutateWords word where g 0 words = words g n words = g (n - 1) (nub $ words >>= mutateWords ) lea = length leata main = do filename <- getArgs wordlist <- readFile $ filename !! 0 let a = (words wordlist) >>= generateAll mapM_ putStrLn a

Daniel,
Sure. If you don't mind that the mutations come in a different order, one thing that works wonders is "sequence",
sequence :: Monad m => [m a] -> m [a]
In particular, for m = [], sequence :: [[a]] -> [[a]]. Then, knowing what sequence does, we can write
import Control.Monad (sequence)
generateAll :: String -> [String] generateAll word = sequence (map f word) where f c = case lookup c leat of Just r -> [c,r] Nothing -> [c]
That's very nice! One question though: In the docs sequence is described as: "Evaluate each action in the sequence from left to right, and collect the results." How is one supposed to deduce what the behavior will be for the list monad (besides looking at the source)? Patrick -- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

Am Dienstag 09 Februar 2010 23:07:55 schrieb Patrick LeBoutillier:
Daniel,
Sure. If you don't mind that the mutations come in a different order, one thing that works wonders is "sequence",
sequence :: Monad m => [m a] -> m [a]
In particular, for m = [], sequence :: [[a]] -> [[a]]. Then, knowing what sequence does, we can write
import Control.Monad (sequence)
generateAll :: String -> [String] generateAll word = sequence (map f word) where f c = case lookup c leat of Just r -> [c,r] Nothing -> [c]
That's very nice!
Thanks. But from a clean-code-higher-level perspective, it's even nicer with your
-- Returns a list of possible characters for c mutateLetter :: Char -> [Char] mutateLetter c = c : (maybeToList $ lookup c leet)
(here is a point where it would be even nicer if lookup had the type lookup :: (Eq a, MonadPlus m) => a -> [(a,b)] -> m b ). The performance-junkie in me would want to look at the core to make sure the maybeToList is eliminated by the compiler, though.
One question though: In the docs sequence is described as:
"Evaluate each action in the sequence from left to right, and collect the results."
How is one supposed to deduce what the behavior will be for the list monad (besides looking at the source)?
Given its polymorphic type sequence :: Monad m => [m a] -> m [a] , what can sequence do? For sequence [] , there's really only one possibility (not involving undefined/error), so sequence [] = return [] Okay, that was the trivial part, now what can be done with nonempty lists? It could ignore the input and return [] in any case, but that wouldn't be useful at all, so we can discard that possibility. What could be usefully done with sequence (m1:ms) ? It has to do something with m1 and something with ms, then combine the results to a list of [a], which it returns. What can it do with m1? Since all that sequence knows about m1 is the type (Monad m => m a), it can't do anything but what's provided by that constraint. Basically, it can only put it on the left of a (>>=). There's on decision to be made, shall it be sequence (m1:ms) = m1 >>= \x -> something with x and ms or something with ms >>= \xs -> (m1 >>= \x -> something with x and xs) ? And what can it do with the tail of the list, ms? Why, sequence it of course. So it's either sequence (m1:ms) = m1 >>= \x -> (sequence ms >>= \xs -> return (fun x xs)) {- sequence (m1:ms) = do x <- m1 xs <- sequence ms return (fun x xs) -} or sequence (m1:ms) = sequence ms >>= \xs -> (m1 >>= \x -> return (fun x xs)) {- sequence (m1:ms) = do xs <- sequence ms x <- m1 return (fun x xs) -} where fun :: forall a. a -> [a] -> [a] Now there's a lot of nonsense you could use for 'fun', fun x xs = reverse (x:xs) fun x xs = x:xs ++ [x,x,x] fun x xs = front ++ x:back where (front,back) = splitAt 17 xs ... , but the most prominent function of type forall a. a -> [a] -> [a] is the only one to be reasonably expected here, so fun x xs = x : xs and the only question that remains is in which order things are chained. That is answered by the docs, left to right, so sequence [] = return [] sequence (m1:ms) = m1 >>= \x -> sequence ms >>= \xs -> return (x:xs) {- sequence (m1:ms) = do x <- m1 xs <- sequence ms return (x:xs) sequence (m1:ms) = m1 >>= \x -> liftM (x :) (sequence ms) -} (or equivalent). Now you need to know how (>>=) is defined for [], namely ys >>= f = concatMap f ys. The short answer is, you can't deduce it wihout knowing the Monad instance for [], and if you know that well enough to not be confused by "evaluate the action" (which takes time), it's fairly straightforward.
Patrick

Daniel,
As usual, thanks a lot for this enlightening response.
Patrick
On Tue, Feb 9, 2010 at 6:31 PM, Daniel Fischer
Am Dienstag 09 Februar 2010 23:07:55 schrieb Patrick LeBoutillier:
Daniel,
Sure. If you don't mind that the mutations come in a different order, one thing that works wonders is "sequence",
sequence :: Monad m => [m a] -> m [a]
In particular, for m = [], sequence :: [[a]] -> [[a]]. Then, knowing what sequence does, we can write
import Control.Monad (sequence)
generateAll :: String -> [String] generateAll word = sequence (map f word) where f c = case lookup c leat of Just r -> [c,r] Nothing -> [c]
That's very nice!
Thanks. But from a clean-code-higher-level perspective, it's even nicer with your
-- Returns a list of possible characters for c mutateLetter :: Char -> [Char] mutateLetter c = c : (maybeToList $ lookup c leet)
(here is a point where it would be even nicer if lookup had the type
lookup :: (Eq a, MonadPlus m) => a -> [(a,b)] -> m b ). The performance-junkie in me would want to look at the core to make sure the maybeToList is eliminated by the compiler, though.
One question though: In the docs sequence is described as:
"Evaluate each action in the sequence from left to right, and collect the results."
How is one supposed to deduce what the behavior will be for the list monad (besides looking at the source)?
Given its polymorphic type
sequence :: Monad m => [m a] -> m [a]
, what can sequence do?
For sequence [] , there's really only one possibility (not involving undefined/error), so sequence [] = return []
Okay, that was the trivial part, now what can be done with nonempty lists? It could ignore the input and return [] in any case, but that wouldn't be useful at all, so we can discard that possibility. What could be usefully done with
sequence (m1:ms) ?
It has to do something with m1 and something with ms, then combine the results to a list of [a], which it returns. What can it do with m1? Since all that sequence knows about m1 is the type (Monad m => m a), it can't do anything but what's provided by that constraint. Basically, it can only put it on the left of a (>>=). There's on decision to be made, shall it be
sequence (m1:ms) = m1 >>= \x -> something with x and ms
or
something with ms >>= \xs -> (m1 >>= \x -> something with x and xs) ? And what can it do with the tail of the list, ms? Why, sequence it of course. So it's either
sequence (m1:ms) = m1 >>= \x -> (sequence ms >>= \xs -> return (fun x xs)) {- sequence (m1:ms) = do x <- m1 xs <- sequence ms return (fun x xs) -} or
sequence (m1:ms) = sequence ms >>= \xs -> (m1 >>= \x -> return (fun x xs)) {- sequence (m1:ms) = do xs <- sequence ms x <- m1 return (fun x xs) -}
where
fun :: forall a. a -> [a] -> [a]
Now there's a lot of nonsense you could use for 'fun',
fun x xs = reverse (x:xs) fun x xs = x:xs ++ [x,x,x] fun x xs = front ++ x:back where (front,back) = splitAt 17 xs ... , but the most prominent function of type forall a. a -> [a] -> [a] is the only one to be reasonably expected here, so
fun x xs = x : xs
and the only question that remains is in which order things are chained. That is answered by the docs, left to right, so
sequence [] = return [] sequence (m1:ms) = m1 >>= \x -> sequence ms >>= \xs -> return (x:xs) {- sequence (m1:ms) = do x <- m1 xs <- sequence ms return (x:xs)
sequence (m1:ms) = m1 >>= \x -> liftM (x :) (sequence ms) -} (or equivalent). Now you need to know how (>>=) is defined for [], namely
ys >>= f = concatMap f ys.
The short answer is, you can't deduce it wihout knowing the Monad instance for [], and if you know that well enough to not be confused by "evaluate the action" (which takes time), it's fairly straightforward.
Patrick
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

Am Mittwoch 10 Februar 2010 00:31:07 schrieb Daniel Fischer:
Am Dienstag 09 Februar 2010 23:07:55 schrieb Patrick LeBoutillier:
Daniel, <snip> One question though: In the docs sequence is described as:
"Evaluate each action in the sequence from left to right, and collect the results."
How is one supposed to deduce what the behavior will be for the list monad (besides looking at the source)? <snip>
Or, of course, you could come from the other end. You want to generate the cartesian product of a list of lists. How do you do that? Easy, for each element of the first list, you stick that to the front of each element of the product of the remaining lists: cartesianProduct :: [[a]] -> [[a]] cartesianProduct (l:ls) = [h:t | h <- l, t <- cartesianProduct ls] -- what to do if there is no first list? The cartesian product of an empty set of sets is a one element set, so cartesianProduct [] = [[]] or, cartesianProduct (l:ls) = do h <- l t <- cartesianProduct ls return (h:t) cartesianProduct [] = return [] -- Hey, that's sequence!!!

Patrick LeBoutillier
Sure. If you don't mind that the mutations come in a different order, one thing that works wonders is "sequence",
sequence :: Monad m => [m a] -> m [a]
In particular, for m = [], sequence :: [[a]] -> [[a]]. Then, knowing what sequence does, we can write
import Control.Monad (sequence)
generateAll :: String -> [String] generateAll word = sequence (map f word) where f c = case lookup c leat of Just r -> [c,r] Nothing -> [c]
That's very nice!
One question though: In the docs sequence is described as:
"Evaluate each action in the sequence from left to right, and collect the results."
How is one supposed to deduce what the behavior will be for the list monad (besides looking at the source)?
Intuitively it's very easy to understand and makes perfect sense, if you interpret the list monad as nondeterminism: sequence [c1,c2,c3] = do x1 <- c1 x2 <- c2 x3 <- c3 return [x1,x2,x3] sequence ["ab", "cd", "ef"] = do x1 <- "ab" x2 <- "cd" x3 <- "ef" return [x1,x2,x3] = ["ace", "acf", "ade", "adf", "bce", "bcf", "bde", "bdf"] In this code x1 stands for all results of c1, x2 for all results of c2 and x3 for all results of c3. It's a convenient way of doing list comprehension without syntactic sugar. See also mapM and replicateM, which have interesting behaviours in the list monad. Greets Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/

I found out I get the posts in my mail and I am clicking in the mailinglist. Therefore I am starting new threads over and over again. My apologies.
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. On Tue, Feb 9, 2010 at 11:07 PM, Patrick LeBoutillier < patrick.leboutillier@gmail.com> wrote:
Daniel,
Sure. If you don't mind that the mutations come in a different order, one thing that works wonders is "sequence",
sequence :: Monad m => [m a] -> m [a]
In particular, for m = [], sequence :: [[a]] -> [[a]]. Then, knowing what sequence does, we can write
import Control.Monad (sequence)
generateAll :: String -> [String] generateAll word = sequence (map f word) where f c = case lookup c leat of Just r -> [c,r] Nothing -> [c]
That's very nice!
One question though: In the docs sequence is described as:
"Evaluate each action in the sequence from left to right, and collect the results."
How is one supposed to deduce what the behavior will be for the list monad (besides looking at the source)?
Patrick
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada
-- Flatliner ICT Service, Email: Edgar.klerks@gmail.com, Tel: +31727851429 Fax: +31848363080 Skype: edgar.klerks Website: flatlinerict.nl Adres: Koelmalaan 258, 1813JD, Alkmaar Nederland
participants (5)
-
Daniel Fischer
-
edgar klerks
-
Ertugrul Soeylemez
-
Krzysztof Skrzętnicki
-
Patrick LeBoutillier