Need some help with an infinite list

Hi guys, I'd like to generate an infinite list, like ["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. "bz", "ca" ...] When I had set out to do this I thought, oh yeah no prob, in a heartbeat. Uhm. Help, pls! Günther PS: I know this should be a no-brainer, sry

One (rather ugly) option is:
tail . map (\y -> showIntAtBase 26 (\x -> chr (x + 96)) y "") $ [0..]
but I'm sure there's a prettier one out there :)
On Tue, Jun 16, 2009 at 8:28 PM, GüŸnther Schmidt
Hi guys,
I'd like to generate an infinite list, like
["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. "bz", "ca" ...]
When I had set out to do this I thought, oh yeah no prob, in a heartbeat.
Uhm.
Help, pls!
Günther
PS: I know this should be a no-brainer, sry
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Here's a way using list comprehensions: Prelude Data.List> take 1000 $ concat.concat $ [ [ replicate n c | c <- ['a'..'z'] ] | n <- [1..] ] "abcdefghijklmnopqrstuvwxyzaabbccddeeffgghhiijjkkllmmnnooppqqrrssttuuvvw wxxyyzzaaabbbcccdddeeefffggghhhiiijjjkkklllmmmnnnooopppqqqrrrssstttuuuvvvwwwxxxyyyzzzaaaabbbbccccddddeeeeffffgggghhhhiiiijjjjkkkkllllmmmmnnnnooooppppqqqqrrrrssssttttuuuuvvvvwwwwxxxxyyyyzzzzaaaaabbbbbcccccdddddeeeeefffffggggghhhhhiiiiijjjjjkkkkklllllmmmmmnnnnnooooopppppqqqqqrrrrrssssstttttuuuuuvvvvvwwwwwxxxxxyyyyyzzzzzaaaaaabbbbbbccccccddddddeeeeeeffffffgggggghhhhhhiiiiiijjjjjjkkkkkkllllllmmmmmmnnnnnnooooooppppppqqqqqqrrrrrrssssssttttttuuuuuuvvvvvvwwwwwwxxxxxxyyyyyyzzzzzzaaaaaaabbbbbbbcccccccdddddddeeeeeeefffffffggggggghhhhhhhiiiiiiijjjjjjjkkkkkkklllllllmmmmmmmnnnnnnnooooooopppppppqqqqqqqrrrrrrrssssssstttttttuuuuuuuvvvvvvvwwwwwwwxxxxxxxyyyyyyyzzzzzzzaaaaaaaabbbbbbbbccccccccddddddddeeeeeeeeffffffffgggggggghhhhhhhhiiiiiiiijjjjjjjjkkkkkkkkllllllllmmmmmmmmnnnnnnnnooooooooppppppppqqqqqqqqrrrrrrrrssssssssttttttttuuuuuuuuvvvvvvvvwwwwwwwwxxxxxxxxyyyyyyyyzzzzzzzzaaaaaaaaabbbbbbbbbcccccccccdddddddddeeeeeeeeefffffffffgggggggggh" -Ross On Jun 16, 2009, at 8:39 PM, Daniel Peebles wrote:
One (rather ugly) option is:
tail . map (\y -> showIntAtBase 26 (\x -> chr (x + 96)) y "") $ [0..]
but I'm sure there's a prettier one out there :)
On Tue, Jun 16, 2009 at 8:28 PM, GüŸnther Schmidt
wrote: Hi guys,
I'd like to generate an infinite list, like
["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. "bz", "ca" ...]
When I had set out to do this I thought, oh yeah no prob, in a heartbeat.
Uhm.
Help, pls!
Günther
PS: I know this should be a no-brainer, sry
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Dear Ross, thanks for your post, you got it almost right, I needed something like "aa", "ab", "ac" ... It seems that Thomas has figured it out. Günther

Oh sorry about that, misread the problem. -Ross On Jun 16, 2009, at 9:16 PM, Günther Schmidt wrote:
Dear Ross,
thanks for your post, you got it almost right, I needed something like "aa", "ab", "ac" ...
It seems that Thomas has figured it out.
Günther
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

letterCombos = map (:[]) ['a'..'z'] ++ concatMap (\c -> map ((c++) . (: [])) ['a'..'z']) letterCombos Not hugely efficient, if you generate the strings in reverse then you can use (c:) rather than ((c++) . (:[])), but that may not be useful to you. Bob On 17 Jun 2009, at 02:28, Günther Schmidt wrote:
Hi guys,
I'd like to generate an infinite list, like
["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. "bz", "ca" ...]
When I had set out to do this I thought, oh yeah no prob, in a heartbeat.
Uhm.
Help, pls!
Günther
PS: I know this should be a no-brainer, sry
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Thomas, thanks, it seems you found it. I find it a bit embarrassing that I was unable to figure this out myself. Günther Thomas Davie schrieb:
letterCombos = map (:[]) ['a'..'z'] ++ concatMap (\c -> map ((c++) . (:[])) ['a'..'z']) letterCombos
Not hugely efficient, if you generate the strings in reverse then you can use (c:) rather than ((c++) . (:[])), but that may not be useful to you.
Bob
On 17 Jun 2009, at 02:28, GüŸnther Schmidt wrote:
Hi guys,
I'd like to generate an infinite list, like
["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. "bz", "ca" ...]
When I had set out to do this I thought, oh yeah no prob, in a heartbeat.
Uhm.
Help, pls!
Günther
PS: I know this should be a no-brainer, sry
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thomas Davie wrote:
letterCombos = map (:[]) ['a'..'z'] ++ concatMap (\c -> map ((c++) . (: [])) ['a'..'z']) letterCombos
Not hugely efficient, if you generate the strings in reverse then you can use (c:) rather than ((c++) . (:[])), but that may not be useful to you.
Bob
I think the following version increases the sharing between the generated strings, and so might be more space-efficient for consumers which hold on to a significant number of them: number :: [a] -> [[a]] number digits = expand [[]] where expand xss = expanded ++ expand expanded where expanded = concatMap (\d -> map (d:) xss) digits binary = number ['0'..'1'] decimal = number ['0'..'9'] alpha = number ['a'..'z'] Regards, Matthew

Günther Schmidt
Hi guys,
I'd like to generate an infinite list, like
["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. "bz", "ca" ...]
If you're happy to have a "" before the "a", you can do this as a fairly cute one-liner in a similar style to this list of Fibonacci numbers. fib = 0:1:[m + n | (m, n) <- zip fib (tail fib)] Regards, Tom

Hi Tom, thanks for that. I remembered reading about that in my earliest haskell days, couldn't find it again and couldn't get it right by myself either. Günther Tom Pledger schrieb:
Günther Schmidt
writes: Hi guys,
I'd like to generate an infinite list, like
["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. "bz", "ca" ...]
If you're happy to have a "" before the "a", you can do this as a fairly cute one-liner in a similar style to this list of Fibonacci numbers.
fib = 0:1:[m + n | (m, n) <- zip fib (tail fib)]
Regards, Tom

this appears to work:
alphabet=map (\x->x:[]) ['a'..'z']
series=alphabet++[x++y|x<-series,y<-alphabet]
On Tue, Jun 16, 2009 at 8:28 PM, GüŸnther Schmidt
Hi guys,
I'd like to generate an infinite list, like
["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. "bz", "ca" ...]
When I had set out to do this I thought, oh yeah no prob, in a heartbeat.
Uhm.
Help, pls!
Günther
PS: I know this should be a no-brainer, sry
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 17 Jun 2009, at 12:28 pm, Günther Schmidt wrote:
Hi guys,
I'd like to generate an infinite list, like
["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. "bz", "ca" ...]
When I had set out to do this I thought, oh yeah no prob, in a heartbeat.
Let me change this slightly. ["0","1",...,"9","00","01",..,"99","000",..."999",...] Does that provide a hint?

Hi Richard, I'd have to guess here :) Maybe, what you have in mind, is: generate an infinite list with numbers from [1 ..], "map" it to base 26? Günther Richard O'Keefe schrieb:
On 17 Jun 2009, at 12:28 pm, GüŸnther Schmidt wrote:
Hi guys,
I'd like to generate an infinite list, like
["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. "bz", "ca" ...]
When I had set out to do this I thought, oh yeah no prob, in a heartbeat.
Let me change this slightly.
["0","1",...,"9","00","01",..,"99","000",..."999",...]
Does that provide a hint?

My solution attempted to exploit this using Numeric.showIntAtBase but
failed because of the lack of 0 prefixes in the numbers. If you can
find a simple way to fix it without duplicating the showIntAtBase
code, I'd be interested!
On Tue, Jun 16, 2009 at 10:01 PM, Richard O'Keefe
On 17 Jun 2009, at 12:28 pm, GüŸnther Schmidt wrote:
Hi guys,
I'd like to generate an infinite list, like
["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. "bz", "ca" ...]
When I had set out to do this I thought, oh yeah no prob, in a heartbeat.
Let me change this slightly.
["0","1",...,"9","00","01",..,"99","000",..."999",...]
Does that provide a hint?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Daniel Peebles
My solution attempted to exploit this using Numeric.showIntAtBase but failed because of the lack of 0 prefixes in the numbers. If you can find a simple way to fix it without duplicating the showIntAtBase code, I'd be interested!
Another advantage of the integer & base method is that it doesn't require a fast-growing amount of memory to keep track of everything between two points in the list. e.g. Hugs> let mywords = "":[w++[ch] | w <- mywords, ch <- ['a'..'z']] in mywords!!1000000 " ERROR - Garbage collection fails to reclaim sufficient space or Hugs> let sss = [""] : [ [ c:s | c <- ['a'..'z'], s <- ss ] | ss <- sss ] in concat (tail sss) !! 1000000 " ERROR - Garbage collection fails to reclaim sufficient space I'm not sure offhand why Reid Barton's replicateM solution doesn't have the same problem. Is it a benefit of the lack of sharing Matthew Brecknell mentioned? Control.Monad> concatMap (\n -> replicateM n ['a'..'z']) [1..] !! 5000000 "jxlks" Regards, Tom

On 17 Jun 2009, at 2:01 pm, Richard O'Keefe wrote: On second thoughts, let strings = "" : [pref++[last] | pref <- strings, last <- ['a'..'z']] in tail strings seems more Haskellish than the stupidly clever counting-based code I had in mind. With this it's much easier to see what it's up to.

At 4:25 PM +1200 6/17/09, Richard O'Keefe wrote:
On 17 Jun 2009, at 2:01 pm, Richard O'Keefe wrote: On second thoughts,
let strings = "" : [pref++[last] | pref <- strings, last <- ['a'..'z']] in tail strings
seems more Haskellish than the stupidly clever counting-based code I had in mind. With this it's much easier to see what it's up to.
And here's a version along similar lines that avoids (++) for greater sharing and efficiency: let sss = [""] : [ [ c:s | c <- ['a'..'z'], s <- ss ] | ss <- sss ] in concat (tail sss)

On Wed, 17 Jun 2009 00:45:56 -0400, you wrote:
And here's a version along similar lines that avoids (++) for greater sharing and efficiency:
let sss = [""] : [ [ c:s | c <- ['a'..'z'], s <- ss ] | ss <- sss ] in concat (tail sss)
Sheer genius! I just inverted it since I like to see the main idea first. letterCombos = concat (tail sss) where sss = [""] : [ [ c:s | c <- ['a'..'z'], s <- ss ] | ss <- sss ] -- Regards, Casey

On Wed, 17 Jun 2009, Richard O'Keefe wrote:
On 17 Jun 2009, at 2:01 pm, Richard O'Keefe wrote: On second thoughts,
let strings = "" : [pref++[last] | pref <- strings, last <- ['a'..'z']] in tail strings
last:pref instead of pref++[last] should do more sharing. You can also write it this way: let strings = "" : Monad.liftM2 (flip (:)) strings ['a'..'z'] in tail strings

On Wed, Jun 17, 2009 at 02:28:55AM +0200, Gü?nther Schmidt wrote:
Hi guys,
I'd like to generate an infinite list, like
["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. "bz", "ca" ...]
I'm surprised everyone is giving clever recursive solutions rather than concatMap (\n -> replicateM n ['a'..'z']) [1..] Regards, Reid

Reid Barton wrote:
I'm surprised everyone is giving clever recursive solutions rather than
concatMap (\n -> replicateM n ['a'..'z']) [1..]
Regards, Reid
Well, you've lost efficient sharing with respect to my previous solution and one other. But it's a fair call, so... tail $ concat $ iterate (map (:) ['a'..'z'] <*>) [[]] Regards, Matthew

On Wed, 17 Jun 2009, Matthew Brecknell wrote:
Reid Barton wrote:
I'm surprised everyone is giving clever recursive solutions rather than
concatMap (\n -> replicateM n ['a'..'z']) [1..]
Regards, Reid
Well, you've lost efficient sharing with respect to my previous solution and one other.
But it's a fair call, so...
tail $ concat $ iterate (map (:) ['a'..'z'] <*>) [[]]
cool

Hi all, you have come up with so many solutions it's embarrassing to admit that I didn't come up with even one. Günther Günther Schmidt schrieb:
Hi guys,
I'd like to generate an infinite list, like
["a", "b", "c" .. "z", "aa", "ab", "ac" .. "az", "ba", "bb", "bc" .. "bz", "ca" ...]
When I had set out to do this I thought, oh yeah no prob, in a heartbeat.
Uhm.
Help, pls!
Günther
PS: I know this should be a no-brainer, sry

On Wed, Jun 17, 2009 at 7:30 PM, GüŸnther Schmidt
Hi all,
you have come up with so many solutions it's embarrassing to admit that I didn't come up with even one.
I have the similarly difficulties, but I found to understand some of these answers, equational reasoning is a very useful tool, I have prepared a blog post for how I worked out some of these answers, here is the draft of it, I hope it can help you too. Oh, if it doesn't help you at all, please let know why :-) lee ==== Understanding Functions Which Use 'instance Monad []' by Equational Reasoning GüŸnther Schmidt asked in Haskell-Cafe how to get a stream like this: ["a", ... , "z", "aa", ... , "az", "ba", ... , "bz", ... ] and people in Haskell-Cafe offer some interesting answer for this question. On the one hand, these answers show the power of Haskell and GHC base libraries, but on the other hand, understanding them is a challenge for Haskell newbie like me. But I found to understand these answers, equational reasoning is very helpful, here is why I think so. Answer 1 (by Matthew Brecknell): concat $ tail $ iterate (map (:) ['a' .. 'z'] <*>) [[]] Well, how does this expression do what we want? concat, tail, iterate, map, are easy, looks like the magic is in (<*>). What's this operator mean? (<*>) comes from class Applicative of Control.Applicative, class Functor f => Applicative f where -- | Lift a value. pure :: a -> f a -- | Sequential application. (<*>) :: f (a -> b) -> f a -> f b and 'instance Applicative []' is instance Applicative [] where pure = return (<*>) = ap ap comes from Control.Monad ap :: (Monad m) => m (a -> b) -> m a -> m b ap = liftM2 id liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r liftM2 f m1 m2 = do { x1 <- m1; x2 <- m2; return (f x1 x2) } so the key to understand (<*>) is understanding the meaning of liftM2. liftM2 uses, hum, do-notation, so by Haskell 98 report, this can be translated to liftM2 f m1 m2 (1.0) = m1 >>= \x1 -> m2 >>= \x2 -> return (f x1 x2) When it is applied to list (you can convince yourself of this by type inference), wee need 'instance Monad []' instance Monad [] where m >>= k = foldr ((++) . k) [] m m >> k = foldr ((++) . (\ _ -> k)) [] m return x = [x] fail _ = [] so liftM2 f m1 m2 = m1 >>= \x1 -> m2 >>= \x2 -> return (f x1 x2) let f1 = \x1 -> m2 >>= \x2 -> return (f x1 x2) f2 = \x2 -> return (f x1 x2) we can write m1 >>= f1 = foldr ((++) . f1) [] m1 m2 >>= f2 = foldr ((++) . f2) [] m2 Now we can see for list m1, m2, how does 'liftM2 f m1 m2' work z1 = [] foreach x1 in (reverse m1); do -- foldr ((++) . f1) [] m1 z2 = [] foreach x2 in (reverse m2); do -- foldr ((++) . f2) [] m2 z2 = [f x1 x2] ++ z2 done z1 = z2 ++ z1 done Now we are ready to see how to apply (<*>): map (:) ['a' .. 'z'] <*> [[]] = (map (:) ['a' .. 'z']) <*> [[]] = [('a':), ..., ('z':)] <*> [[]] -- misuse of [...] notation = ap [('a':), ..., ('z':)] [[]] = liftM2 id [('a':), ..., ('z':)] [[]] = [('a':), ..., ('z':)] >>= \x1 -> [[]] >>= \x2 -> return (id x1 x2) Here x1 bind to ('z':), ..., ('a':) in turn, x2 always bind to [], and noticed that return (id ('z':) []) -- f = id; x1 = ('a':); x2 = [] = return (('z':) []) = return ((:) 'z' []) = return "z" = ["z"] we have map (:) ['a', .., 'z'] <*> [[]] = liftM2 id [('a':), ..., ('z':)] [[]] = ["a", ..., "z"] (If you can't follow the this, work through the definition of foldr step by step will be very helpful.) map (:) ['a', .., 'z'] <*> (map (:) ['a', .., 'z'] <*> [[]]) = map (:) ['a', .., 'z'] <*> ["a", .., "z"] = liftM2 id [('a':), ..., ('z':)] ["a", ..., "z"] = ["aa", ..., "az", "ba", ..., "bz", ..., "za", ..., "zz"] Now it's easy to know what we get from iterate (map (:) ['a' .. 'z'] <*>) [[]] = [[], f [[]], f (f [[]]), ...] -- f = map (:) ['a' .. 'z'] <*> so concat $ tail $ iterate (map (:) ['a' .. 'z'] <*>) [[]] is exactly what we want. Understanding Haskell codes by equational reasoning could be a very tedious process, but it's also a very helpful and instructive process for the beginners, because it make you think slowly, check the computation process step by step, just like the compiler does. And in my opinion, this is exactly what a debugger does. Answer 2 (by Reid Barton): concatMap (\n -> replicateM n ['a'..'z']) [1..] In this solution, the hardest part is replicatM, which come from Control.Monad replicateM :: (Monad m) => Int -> m a -> m [a] replicateM n x = sequence (replicate n x) sequence :: Monad m => [m a] -> m [a] sequence ms = foldr k (return []) ms where k m m' = do { x <- m; xs <- m'; return (x:xs) } recall the defintion of liftM2: liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r liftM2 f m1 m2 = do { x1 <- m1; x2 <- m2; return (f x1 x2) } so k in definition of sequence is an application of liftM2, and sequence itself is a normal foldr. Exercise 1: Prove that for n >= 1 replicateM n ['a' .. 'z'] = (iterate (map (:) ['a' .. 'z'] <*>) [[]]) !! n or more generally replicateM = \n xs -> (iterate (map (:) xs <*>) [[]]) !! n Answer: replicateM 1 ['a' .. 'z'] = sequence [ ['a' .. 'z'] ] = foldr k (return []) [['a' .. 'z']] = k ['a' .. 'z'] [[]] -- return [] = [[]] = liftM2 (:) ['a' .. 'z'] [[]] = map (:) ['a' .. 'z'] <*> [[]] = ["a", ..., "z"] replicateM 2 ['a' .. 'z'] = sequence [['a' .. 'z'], ['a' .. 'z']] = foldr k [[]] [['a' .. 'z'], ['a' .. 'z']] = k ['a' .. 'z'] (k ['a' .. 'z'] [[]]) = k ['a' .. 'z'] (f [[]]) -- f = map (:) ['a' .. 'z'] <*> = f (f [[]])

On Thu, 2009-06-18 at 23:57 +0800, Lee Duhem wrote:
[...] I have prepared a blog post for how I worked out some of these answers, here is the draft of it, I hope it can help you too.
Nice post! Certainly, pen-and-paper reasoning like this is a very good way to develop deeper intuitions.
Answer 1 (by Matthew Brecknell):
concat $ tail $ iterate (map (:) ['a' .. 'z'] <*>) [[]]
I actually said "tail $ concat $ iterate ...", because I think the initial empty string is logically part of the sequence. Tacking "tail" on the front then produces the subsequence requested by the OP. I should have given more credit to Reid for this solution. I'm always delighted to see people using monadic combinators (like replicateM) in the list monad, because I so rarely think to use them this way. Sadly, my understanding of these combinators is still somewhat stuck in IO, where I first learned them. I never would have thought to use <*> this way if I had not seen Reid's solution first. Also, for many applications, a non-sharing version like Reid's is really what you want. Sharing versions have to keep references to old strings around to reuse later, and so are really only appropriate for applications which would keep them in memory anyway. Regards, Matthew

On Fri, Jun 19, 2009 at 6:17 AM, Matthew Brecknell
On Thu, 2009-06-18 at 23:57 +0800, Lee Duhem wrote:
[...] I have prepared a blog post for how I worked out some of these answers, here is the draft of it, I hope it can help you too.
Nice post! Certainly, pen-and-paper reasoning like this is a very good way to develop deeper intuitions.
Answer 1 (by Matthew Brecknell):
concat $ tail $ iterate (map (:) ['a' .. 'z'] <*>) [[]]
I actually said "tail $ concat $ iterate ...", because I think the initial empty string is logically part of the sequence. Tacking "tail" on the front then produces the subsequence requested by the OP.
Yes, I changed your solution from "tail $ concat $ iterate ..." to "concat $ tail $ iterate ...", because I think cut useless part out early is good idea, forgot to mention that, sorry.
I should have given more credit to Reid for this solution. I'm always delighted to see people using monadic combinators (like replicateM) in the list monad, because I so rarely think to use them this way. Sadly, my understanding of these combinators is still somewhat stuck in IO, where I first learned them. I never would have thought to use <*> this way if I had not seen Reid's solution first.
Actually, I first figure out how Reid's solution works, then figure out yours. After that, I found, for me, your solution's logic is easier to understand, so I take it as my first example. As I said at the end, or as I'll said at the end, Reid' solution and yours are the same (except effective) lee

could someone explain sharing?
In the code below, allstrings2 is 6X as fast as allstrings. I assume
because of sharing, but I don't intuitively see a reason why.
can someone give me some pointers, perhaps using debug.trace or other
tools (profiling?) to show where the first version is being
inefficient?
***********
letters = ['a'..'z']
strings 0 = [""]
strings n = [ c : s | c <- letters, s <- strings (n-1) x ]
allstrings = concat $ map strings [1..]
allstrings2 = let sss = [""] : [ [ c:s | c <- letters, s <- ss ] | ss <- sss ]
in concat $ tail sss
t = allstrings !! wanted
t2 = allstrings2 !! wanted
wanted = (10^2)
2009/6/18 Lee Duhem
On Fri, Jun 19, 2009 at 6:17 AM, Matthew Brecknell
wrote: On Thu, 2009-06-18 at 23:57 +0800, Lee Duhem wrote:
[...] I have prepared a blog post for how I worked out some of these answers, here is the draft of it, I hope it can help you too.
Nice post! Certainly, pen-and-paper reasoning like this is a very good way to develop deeper intuitions.
Answer 1 (by Matthew Brecknell):
concat $ tail $ iterate (map (:) ['a' .. 'z'] <*>) [[]]
I actually said "tail $ concat $ iterate ...", because I think the initial empty string is logically part of the sequence. Tacking "tail" on the front then produces the subsequence requested by the OP.
Yes, I changed your solution from "tail $ concat $ iterate ..." to "concat $ tail $ iterate ...", because I think cut useless part out early is good idea, forgot to mention that, sorry.
I should have given more credit to Reid for this solution. I'm always delighted to see people using monadic combinators (like replicateM) in the list monad, because I so rarely think to use them this way. Sadly, my understanding of these combinators is still somewhat stuck in IO, where I first learned them. I never would have thought to use <*> this way if I had not seen Reid's solution first.
Actually, I first figure out how Reid's solution works, then figure out yours. After that, I found, for me, your solution's logic is easier to understand, so I take it as my first example. As I said at the end, or as I'll said at the end, Reid' solution and yours are the same (except effective)
lee _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Well, I'm hardly the one knowing GHC internals, but... In allstrings you continue calling "strings" with same arguments again and again. Don't fool yourself, it's not going to automagically memorize what you were doing before. In fact, I'd expect much more speed loss. If you increase your "wanted" constant, you'll probably notice it. Anyway, you allstrings2 is much nicer - the problem you're solving has nothing to do with numbers, so "map whatever [1..]" seems out of place. On 20 Jun 2009, at 22:16, Thomas Hartman wrote:
could someone explain sharing?
In the code below, allstrings2 is 6X as fast as allstrings. I assume because of sharing, but I don't intuitively see a reason why.
can someone give me some pointers, perhaps using debug.trace or other tools (profiling?) to show where the first version is being inefficient?
***********
letters = ['a'..'z']
strings 0 = [""] strings n = [ c : s | c <- letters, s <- strings (n-1) x ]
allstrings = concat $ map strings [1..]
allstrings2 = let sss = [""] : [ [ c:s | c <- letters, s <- ss ] | ss <- sss ] in concat $ tail sss
t = allstrings !! wanted t2 = allstrings2 !! wanted
wanted = (10^2)
2009/6/18 Lee Duhem
: On Fri, Jun 19, 2009 at 6:17 AM, Matthew Brecknell
wrote: On Thu, 2009-06-18 at 23:57 +0800, Lee Duhem wrote:
[...] I have prepared a blog post for how I worked out some of these answers, here is the draft of it, I hope it can help you too.
Nice post! Certainly, pen-and-paper reasoning like this is a very good way to develop deeper intuitions.
Answer 1 (by Matthew Brecknell):
concat $ tail $ iterate (map (:) ['a' .. 'z'] <*>) [[]]
I actually said "tail $ concat $ iterate ...", because I think the initial empty string is logically part of the sequence. Tacking "tail" on the front then produces the subsequence requested by the OP.
Yes, I changed your solution from "tail $ concat $ iterate ..." to "concat $ tail $ iterate ...", because I think cut useless part out early is good idea, forgot to mention that, sorry.
I should have given more credit to Reid for this solution. I'm always delighted to see people using monadic combinators (like replicateM) in the list monad, because I so rarely think to use them this way. Sadly, my understanding of these combinators is still somewhat stuck in IO, where I first learned them. I never would have thought to use <*> this way if I had not seen Reid's solution first.
Actually, I first figure out how Reid's solution works, then figure out yours. After that, I found, for me, your solution's logic is easier to understand, so I take it as my first example. As I said at the end, or as I'll said at the end, Reid' solution and yours are the same (except effective)
lee _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thomas Hartman wrote:
could someone explain sharing?
In the code below, allstrings2 is 6X as fast as allstrings. I assume because of sharing, but I don't intuitively see a reason why.
can someone give me some pointers, perhaps using debug.trace or other tools (profiling?) to show where the first version is being inefficient?
***********
letters = ['a'..'z']
strings 0 = [""] strings n = [ c : s | c <- letters, s <- strings (n-1) x ]
allstrings = concat $ map strings [1..]
allstrings2 = let sss = [""] : [ [ c:s | c <- letters, s <- ss ] | ss <- sss ] in concat $ tail sss
It's a dynamic-programming problem. Let's reword this in terms of fibonnaci: fibs = map fib [0..] where fib 0 = 0 fib 1 = 1 fib n = fib (n-1) + fib (n-2) This is essentially what allstrings is doing. We have a basic function fib/strings and we use it to "count down" from our seed input to the value we want. But, because fib/strings is a pure function, it will always give equivalent output for the same input, and so once we hit some query we've answered before we'd like to just stop. But this version won't stop, it'll count all the way down to the bottom. Haskell doesn't automatically memoize functions, so it's a key point that the values are only "equivalent". With allstrings2 we do memoization and take it a step further to return the "identical" answer, since we keep a copy of the answers we've given out before. The fibs variation is: fibs = 0 : 1 : zipWith (+) fibs (tail fibs) Because we're defining fibs recursively in terms of itself, to get the next element of the stream we only need to keep track of the previous two answers we've given out. Similarly for allstrings2 because sss is defined in terms of itself it's always producing elements one step before it needs them. More particularly, because the recursion has "already been done" producing the next element is just a matter of applying (+) or applying [ c:s | c <- letters, s <- ss ] and we don't need to repeat the recursion. -- Live well, ~wren

Thomas Hartman wrote:
could someone explain sharing?
A good tool for visualising the difference between shared and non-shared results would be vacuum, using one of its front ends, vacuum-cairo or vacuum-ubigraph. http://hackage.haskell.org/package/vacuum http://hackage.haskell.org/package/vacuum-cairo http://hackage.haskell.org/package/vacuum-ubigraph To see sharing, you will need to view a set of outputs (not just one string). To keep the graph to a manageable size, use a smaller alphabet: digits = "01" -- All words of length n, with shared substrings shared :: Int -> [String] shared n = sss !! n where sss = [""] : [ [ c:s | c <- digits, s <- ss ] | ss <- sss ] -- All words of length n, with unshared substrings unshared :: Int -> [String] unshared 0 = [""] unshared n = [ c:s | c <- digits, s <- unshared (n-1) ] And then in GHCi: Vacuum.Cairo> shared 3 == unshared 3 True Vacuum.Cairo> view $ shared 3 Vacuum.Cairo> view $ unshared 3 I'd send some PNGs, except my vacuum installation is currently broken. Perhaps someone else can? Regards, Matthew
participants (16)
-
Casey Hawthorne
-
Daniel Peebles
-
Dean Herington
-
Günther Schmidt
-
Henning Thielemann
-
José Prous
-
Lee Duhem
-
Matthew Brecknell
-
Miguel Mitrofanov
-
Reid Barton
-
Richard O'Keefe
-
Ross Mellgren
-
Thomas Davie
-
Thomas Hartman
-
Tom Pledger
-
wren ng thornton