
Hi, I'ld like to generate a list (of lists) that contains all combinations of natural numbers stored in another list. It should work like a combination-lock. E.g.: [2,2] -> [[0,0],[0,1],[0,2],[1,0],[1,1],[1,2],[2,0],[2,1],[2,2]] If I know the length 'l' of the 'locklist', I can solve the problem via generators. E.g.: l = 2: [[a,b] | a <- [0..locklist!!0], b <- [0..locklist!!1]] But if the length is unknown (because it's dynamic) this solutions (of course) fails. Is it possible to solve this problem in haskell in an elegant way? Thanks Flo

Just make the function recursive. There is a simple relation between, l [a,b,c] and l [b,c] Tom On Tue, 10 Aug 2004 14:01, Florian Boehl wrote:
Hi,
I'ld like to generate a list (of lists) that contains all combinations of natural numbers stored in another list. It should work like a combination-lock. E.g.:
[2,2] -> [[0,0],[0,1],[0,2],[1,0],[1,1],[1,2],[2,0],[2,1],[2,2]]
If I know the length 'l' of the 'locklist', I can solve the problem via generators. E.g.:
l = 2: [[a,b] | a <- [0..locklist!!0], b <- [0..locklist!!1]]
But if the length is unknown (because it's dynamic) this solutions (of course) fails. Is it possible to solve this problem in haskell in an elegant way?
Thanks
Flo _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Better hope you get what you want before you stop wanting it.

At 06:01 10/08/04 +0200, Florian Boehl wrote:
Hi,
I'ld like to generate a list (of lists) that contains all combinations of natural numbers stored in another list. It should work like a combination-lock. E.g.:
[2,2] -> [[0,0],[0,1],[0,2],[1,0],[1,1],[1,2],[2,0],[2,1],[2,2]]
If I know the length 'l' of the 'locklist', I can solve the problem via generators. E.g.:
l = 2: [[a,b] | a <- [0..locklist!!0], b <- [0..locklist!!1]]
But if the length is unknown (because it's dynamic) this solutions (of course) fails. Is it possible to solve this problem in haskell in an elegant way?
I can think of one using 'sequence', 'map' and a lambda abstraction. [[ Main> combo [2,3,4] [[1,1,1],[1,1,2],[1,1,3],[1,1,4],[1,2,1],[1,2,2],[1,2,3],[1,2,4],[1,3,1],[1,3,2] ,[1,3,3],[1,3,4],[2,1,1],[2,1,2],[2,1,3],[2,1,4],[2,2,1],[2,2,2],[2,2,3],[2,2,4] ,[2,3,1],[2,3,2],[2,3,3],[2,3,4]] ]] (It's a trivial to tweak the range to start from 0.) #g ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

G'day all. At 06:01 10/08/04 +0200, Florian Boehl wrote:
If I know the length 'l' of the 'locklist', I can solve the problem via generators. E.g.:
l = 2: [[a,b] | a <- [0..locklist!!0], b <- [0..locklist!!1]]
But if the length is unknown (because it's dynamic) this solutions (of course) fails. Is it possible to solve this problem in haskell in an elegant way?
This is a transformation that it's useful to know about: [ E | x <- Xs, y <- Ys ] = concat [ [ E | y <- Ys ] | x <- Xs ] Whether or not it's any use to you is another matter. :-) Cheers, Andrew Bromage

On Tue, 10 Aug 2004, Florian Boehl wrote:
I'ld like to generate a list (of lists) that contains all combinations of natural numbers stored in another list. It should work like a combination-lock. E.g.:
[2,2] -> [[0,0],[0,1],[0,2],[1,0],[1,1],[1,2],[2,0],[2,1],[2,2]]
I have written a similar routine: {- | Compositional power of a function, i.e. apply the function n times to a value. -} nest :: Int -> (a -> a) -> a -> a nest 0 _ x = x nest n f x = f (nest (n-1) f x) {- | Generate all possibilities to select n elements out of the list x -} variate :: Int -> [a] -> [[a]] variate n x = nest n (\y -> concatMap (\z -> map (z:) y) x) [[]] Prelude> variate 2 ['a','b','c'] ["aa","ab","ac","ba","bb","bc","ca","cb","cc"] (I'm not sure if it is correct to translate the German word "Variationen" to "variations".) To make it complete: {- | Generate list of all permutations of the input list. The list is sorted lexicographically. -} permute :: [a] -> [[a]] permute [] = [[]] permute x = concatMap (\(y, z:zs) -> map (z:) (permute (y++zs))) (init (zip (inits x) (tails x)))

Here's my version: combs [] = [] combs [n] = [[i] | i <- [0..n]] combs (n:r) = let combsr = combs r in [i:cr | i <- [0..n], cr <- combsr] - Lyle Florian Boehl wrote:
Hi,
I'ld like to generate a list (of lists) that contains all combinations of natural numbers stored in another list. It should work like a combination-lock. E.g.:
[2,2] -> [[0,0],[0,1],[0,2],[1,0],[1,1],[1,2],[2,0],[2,1],[2,2]]
If I know the length 'l' of the 'locklist', I can solve the problem via generators. E.g.:
l = 2: [[a,b] | a <- [0..locklist!!0], b <- [0..locklist!!1]]
But if the length is unknown (because it's dynamic) this solutions (of course) fails. Is it possible to solve this problem in haskell in an elegant way?
Thanks
Flo _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, 11 Aug 2004, Lyle Kopnicky wrote:
Here's my version:
combs [] = [] combs [n] = [[i] | i <- [0..n]] combs (n:r) = let combsr = combs r in [i:cr | i <- [0..n], cr <- combsr]
Since there is one zero combination, it should be
combs [] = [[]]
Then you can also remove the definition of combs [n] . What is the advantage of introducing 'combsr' instead of using 'combs r' immediately?

Oops, just realised that I didn't include the mailing list in my original reply to Florian -- here was my reply: --------- Hi, I would write it as one of the following, ---- keys [] = [[]] keys (x:xs) = [0..x] >>= (\k -> map (k:) (keys xs)) -- or, keys' [] = [[]] keys' (x:xs) = do { k <- [0..x] ; map (k:) (keys' xs) } -- or, keys'' [] = [[]] keys'' (x:xs) = concat [map (k:) (keys'' xs) | k <- [0..x]] -- or, keys''' [] = [[]] keys''' (x:xs) = concat (map (\k -> map (k:) (keys''' xs)) [0..x]) ---- Each of which does what I think you want. The first two use the fact that lists are a monad, using bind and do notation respectively. (You might have a look at http://www.haskell.org/hawiki/MonadsAsContainers for more information and intuition about what's going on there.) The third makes use of a list comprehension, and the fourth is written using just list functions without any special syntax. The general idea is that to construct keys (x:xs) you add each of [0..x] to the front of each list produced by keys xs. Which of these is most elegant is up to you :) - Cale

Hi Cale, On Wed, Aug 11, 2004 at 02:38:51PM -0400, Cale Gibbard wrote:
I would write it as one of the following, ---- keys [] = [[]] keys (x:xs) = [0..x] >>= (\k -> map (k:) (keys xs)) -- or, keys' [] = [[]] keys' (x:xs) = do { k <- [0..x] ; map (k:) (keys' xs) } -- or, keys'' [] = [[]] keys'' (x:xs) = concat [map (k:) (keys'' xs) | k <- [0..x]] -- or, keys''' [] = [[]] keys''' (x:xs) = concat (map (\k -> map (k:) (keys''' xs)) [0..x]) ---- Thanks for your detailed reply. I chose the third function, because I understood it immediatly (and it's shorter than the fourth ;) ). Unfortunately I'm not really common to monads yet (but willing to learn of course).
Bye Flo

Henning Thielemann wrote:
On Wed, 11 Aug 2004, Lyle Kopnicky wrote:
Here's my version:
combs [] = [] combs [n] = [[i] | i <- [0..n]] combs (n:r) = let combsr = combs r in [i:cr | i <- [0..n], cr <- combsr]
Since there is one zero combination, it should be
combs [] = [[]]
Ah, yes. I knew I must be missing something. That would be a lock which has no numbers on it, but can be opened at any time.
Then you can also remove the definition of combs [n] .
What is the advantage of introducing 'combsr' instead of using 'combs r' immediately?
I initially did that to save recalculation, but later shifted things around, and now I see there is no need for it. Thanks. Here is the improved version: combs [] = [[]] combs (n:r) = [i:cr | i <- [0..n], cr <- combs r] - Lyle

Well, as far as that goes, we can shave off a little bit (around 7%) this way: combs = mapM (\k->[0..k]) (As a bonus, it's even a bit more cryptic/symbolic, in the fine tradition of APL one-liner character-shavings.) But who's counting? :) :) :) -- Fritz Ruehr On Aug 11, 2004, at 3:22 PM, Mike Gunter wrote:
Why so long-winded :-)?
combs = mapM (enumFromTo 0)
mike
Lyle Kopnicky
writes: ... Here is the improved version:
combs [] = [[]] combs (n:r) = [i:cr | i <- [0..n], cr <- combs r] ...
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Even shorter: c=mapM(\k->[0..k]) - Lyle Fritz Ruehr wrote:
Well, as far as that goes, we can shave off a little bit (around 7%) this way:
combs = mapM (\k->[0..k])
(As a bonus, it's even a bit more cryptic/symbolic, in the fine tradition of APL one-liner character-shavings.)
But who's counting? :) :) :)
-- Fritz Ruehr
participants (10)
-
ajb@spamcop.net
-
Cale Gibbard
-
Florian Boehl
-
Fritz Ruehr
-
Graham Klyne
-
Henning Thielemann
-
lists@qseep.net
-
Lyle Kopnicky
-
Mike Gunter
-
Thomas L. Bevan