
Wizards, I've the following small piece of code \begin{code} pairs :: [a] -> [b] -> [[(a, b)]] pairs l1 = map (zip l1) . takeKFromN l1 takeKFromN :: [b] -> [a] -> [[a]] takeKFromN s l = case s of [] -> [[]] _ : r -> [ a : b | a <- l, b <- takeKFromN r l] \end{code} I have a predicate: p :: (a, b) -> Bool and I want to keep only those results of pairs which fulfill "all p". I do so currently by "filter (all p) (pairs l1 l2)", but I want to generate the beginning of this pair lists more efficiently, because the result list of pairs may become very large, soon: length (pairs l1 l2) == length l2 ^ length l1 Any ideas (or other hints) to improve the code? "pairs" computes all different mappings from all elements of l1 to some elements of l2. "takeKFromN" computes all possible sequences of length l1 with elements from l2. I somehow want to integrate the predicate into the generation. Cheers Christian

Am Mittwoch 02 Dezember 2009 14:49:21 schrieb Christian Maeder:
Wizards,
I've the following small piece of code
\begin{code} pairs :: [a] -> [b] -> [[(a, b)]] pairs l1 = map (zip l1) . takeKFromN l1
takeKFromN :: [b] -> [a] -> [[a]] takeKFromN s l = case s of [] -> [[]] _ : r -> [ a : b | a <- l, b <- takeKFromN r l] \end{code}
I have a predicate: p :: (a, b) -> Bool
and I want to keep only those results of pairs which fulfill "all p".
takeKFromNWithP :: (a -> b -> Bool) -> [a] -> [b] -> [[b]] takeKFromNWithP p s l = case s of (h:t) -> [x:ys | x <- filter (p h) l, ys <- takeKFromNWithP p t l] [] -> [[]] filteredPairs :: (a -> b -> Bool) -> [a] -> [b] -> [[(a,b)]] filteredPairs p l1 = map (zip l1) . takeKFromNWithP l1 or, in one go: funkyName :: (a -> b -> Bool) -> [a] -> [b] -> [[(a,b)]] funkyName p s l = case s of (h:t) -> [(h,a):ys | a <- filter (p h) l, ys <- funkyName p t l] [] -> [[]]
I do so currently by "filter (all p) (pairs l1 l2)", but I want to generate the beginning of this pair lists more efficiently, because the result list of pairs may become very large, soon:
length (pairs l1 l2) == length l2 ^ length l1
Any ideas (or other hints) to improve the code?
"pairs" computes all different mappings from all elements of l1 to some elements of l2. "takeKFromN" computes all possible sequences of length l1 with elements from l2.
I somehow want to integrate the predicate into the generation.
Cheers Christian

Am Mittwoch 02 Dezember 2009 17:10:02 schrieb Christian Maeder:
Thanks a lot, works as expected and is super short!
You're welcome. However, according to a couple of tests, the "funkyName" version is somewhat faster and allocates less.
Cheers Christian
Daniel Fischer schrieb:
Or:
fpairs p s l = sequence [[(a,b) | b <- filter (p a) l] | a <- s]

Daniel Fischer schrieb:
However, according to a couple of tests, the "funkyName" version is somewhat faster and allocates less.
My timing tests showed that your fpairs version is fastest. (first argument "True" selects filteredPairs, "False" funkyName) My initial version "myf" is almost unusable. C. (code attached) maeder@leibniz:~/haskell/examples> ghc --make -O2 FilteredPairs.hs [1 of 1] Compiling Main ( FilteredPairs.hs, FilteredPairs.o ) Linking FilteredPairs ... maeder@leibniz:~/haskell/examples> time ./FilteredPairs True EQ 5000 5000 real 0m0.567s user 0m0.536s sys 0m0.020s maeder@leibniz:~/haskell/examples> time ./FilteredPairs False EQ 5000 5000 real 0m0.819s user 0m0.796s sys 0m0.012s

Am Mittwoch 02 Dezember 2009 18:54:51 schrieb Christian Maeder:
Daniel Fischer schrieb:
However, according to a couple of tests, the "funkyName" version is somewhat faster and allocates less.
My timing tests showed that your fpairs version is fastest. (first argument "True" selects filteredPairs, "False" funkyName)
I can confirm that for your test; still funkyName allocates less: ./FilteredPairs True EQ 5000 +RTS -sstderr 5000 1,810,136 bytes allocated in the heap 1,160,412 bytes copied during GC 517,964 bytes maximum residency (1 sample(s)) 16,932 bytes maximum slop 2 MB total memory in use (0 MB lost due to fragmentation) Generation 0: 2 collections, 0 parallel, 0.01s, 0.01s elapsed Generation 1: 1 collections, 0 parallel, 0.00s, 0.00s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 0.44s ( 0.44s elapsed) GC time 0.01s ( 0.01s elapsed) ./FilteredPairs False EQ 5000 +RTS -sstderr 5000 1,432,328 bytes allocated in the heap 974,252 bytes copied during GC 441,064 bytes maximum residency (1 sample(s)) 27,608 bytes maximum slop 2 MB total memory in use (0 MB lost due to fragmentation) Generation 0: 2 collections, 0 parallel, 0.00s, 0.00s elapsed Generation 1: 1 collections, 0 parallel, 0.00s, 0.00s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 0.84s ( 0.84s elapsed) GC time 0.01s ( 0.01s elapsed) ./FilteredPairs True GT 5000 +RTS -sstderr 5000 10,961,984 bytes allocated in the heap 12,164,420 bytes copied during GC 3,046,920 bytes maximum residency (4 sample(s)) 25,836 bytes maximum slop 7 MB total memory in use (0 MB lost due to fragmentation) Generation 0: 16 collections, 0 parallel, 0.04s, 0.04s elapsed Generation 1: 4 collections, 0 parallel, 0.03s, 0.04s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 0.23s ( 0.24s elapsed) GC time 0.08s ( 0.09s elapsed) ./FilteredPairs False GT 5000 +RTS -sstderr 5000 5,246,036 bytes allocated in the heap 5,185,808 bytes copied during GC 1,699,744 bytes maximum residency (2 sample(s)) 27,612 bytes maximum slop 4 MB total memory in use (0 MB lost due to fragmentation) Generation 0: 8 collections, 0 parallel, 0.02s, 0.02s elapsed Generation 1: 2 collections, 0 parallel, 0.02s, 0.01s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 0.44s ( 0.45s elapsed) GC time 0.04s ( 0.03s elapsed)
My initial version "myf" is almost unusable.
C.
(code attached)
maeder@leibniz:~/haskell/examples> ghc --make -O2 FilteredPairs.hs [1 of 1] Compiling Main ( FilteredPairs.hs, FilteredPairs.o ) Linking FilteredPairs ... maeder@leibniz:~/haskell/examples> time ./FilteredPairs True EQ 5000 5000
real 0m0.567s user 0m0.536s sys 0m0.020s maeder@leibniz:~/haskell/examples> time ./FilteredPairs False EQ 5000 5000
real 0m0.819s user 0m0.796s sys 0m0.012s
But with a different test, funkyName is considerably faster: ./pairs 1 8 20 +RTS -sstderr -A150M 5529600 899,189,488 bytes allocated in the heap 72,912,040 bytes copied during GC 28,074,964 bytes maximum residency (2 sample(s)) 465,800 bytes maximum slop 200 MB total memory in use (2 MB lost due to fragmentation) Generation 0: 4 collections, 0 parallel, 0.17s, 0.21s elapsed Generation 1: 2 collections, 0 parallel, 0.36s, 0.39s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 0.72s ( 0.95s elapsed) GC time 0.52s ( 0.60s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 1.25s ( 1.56s elapsed) %GC time 41.9% (38.8% elapsed) Alloc rate 1,235,074,051 bytes per MUT second Productivity 57.8% of total user, 46.5% of total elapsed ./pairs 2 8 20 +RTS -sstderr -A150M 5529600 651,866,696 bytes allocated in the heap 76,108,204 bytes copied during GC 28,075,464 bytes maximum residency (2 sample(s)) 465,248 bytes maximum slop 200 MB total memory in use (2 MB lost due to fragmentation) Generation 0: 3 collections, 0 parallel, 0.18s, 0.20s elapsed Generation 1: 2 collections, 0 parallel, 0.38s, 0.41s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 0.61s ( 0.77s elapsed) GC time 0.56s ( 0.61s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 1.17s ( 1.38s elapsed) %GC time 47.6% (44.0% elapsed) Alloc rate 1,065,075,527 bytes per MUT second Productivity 52.1% of total user, 44.0% of total elapsed ./pairs 3 8 20 +RTS -sstderr -A150M 5529600 516,244,640 bytes allocated in the heap 84,175,532 bytes copied during GC 28,074,916 bytes maximum residency (2 sample(s)) 465,940 bytes maximum slop 200 MB total memory in use (2 MB lost due to fragmentation) Generation 0: 2 collections, 0 parallel, 0.16s, 0.17s elapsed Generation 1: 2 collections, 0 parallel, 0.38s, 0.41s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 0.42s ( 0.60s elapsed) GC time 0.53s ( 0.58s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 0.95s ( 1.18s elapsed) %GC time 56.1% (49.0% elapsed) Alloc rate 1,240,892,153 bytes per MUT second Productivity 43.9% of total user, 35.1% of total elapsed ./pairs 4 8 20 +RTS -sstderr -A150M 5529600 271,711,724 bytes allocated in the heap 28,059,740 bytes copied during GC 28,075,488 bytes maximum residency (1 sample(s)) 461,344 bytes maximum slop 172 MB total memory in use (1 MB lost due to fragmentation) Generation 0: 1 collections, 0 parallel, 0.00s, 0.00s elapsed Generation 1: 1 collections, 0 parallel, 0.18s, 0.21s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 0.24s ( 0.41s elapsed) GC time 0.18s ( 0.21s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 0.43s ( 0.62s elapsed) %GC time 43.0% (33.3% elapsed) Alloc rate 1,113,504,186 bytes per MUT second Productivity 57.0% of total user, 39.1% of total elapsed Which one is faster depends on what you do, it seems.

Daniel Fischer schrieb:
Am Mittwoch 02 Dezember 2009 18:54:51 schrieb Christian Maeder:
Daniel Fischer schrieb:
However, according to a couple of tests, the "funkyName" version is somewhat faster and allocates less. My timing tests showed that your fpairs version is fastest.
Interesting. Using a faster version of "sequence": http://www.haskell.org/pipermail/haskell-cafe/2009-November/069491.html \begin{code} allPossibilities :: [[a]] -> [[a]] allPossibilities [] = [[]] allPossibilities (l:ls) = [ x : xs | x <- l, xs <- allPossibilities ls] funkyName :: (a -> b -> Bool) -> [a] -> [b] -> [[(a, b)]] funkyName p s l = case s of h : t -> [(h, a) : ys | a <- filter (p h) l, ys <- funkyName p t l] [] -> [[]] fpairs :: (a -> b -> Bool) -> [a] -> [b] -> [[(a, b)]] fpairs p s l = allPossibilities [[(a, b) | b <- filter (p a) l] | a <- s] \end{code} fpairs and funkyName are about equally fast. Cheers Christian

On Fri, Dec 4, 2009 at 6:42 AM, Christian Maeder
Daniel Fischer schrieb:
Am Mittwoch 02 Dezember 2009 18:54:51 schrieb Christian Maeder:
Daniel Fischer schrieb:
However, according to a couple of tests, the "funkyName" version is somewhat faster and allocates less. My timing tests showed that your fpairs version is fastest.
Interesting. Using a faster version of "sequence":
http://www.haskell.org/pipermail/haskell-cafe/2009-November/069491.html
\begin{code} allPossibilities :: [[a]] -> [[a]] allPossibilities [] = [[]] allPossibilities (l:ls) = [ x : xs | x <- l, xs <- allPossibilities ls]
I am confused. This is exactly sequence. How is this a faster version? Other than maybe avoiding some dictionary-passing? Incidentally there is a "better" version of sequence for finding products of lists: allPossibilities :: [[a]] -> [[a]] allPossibilities [] = [[]] allPossibilities (l:ls) = [ x : xs | xs <- allPossibilites ls, x <- l ] Or, the general form (I don't know of a use other than for lists, however): sequence' :: Applicative f => [f a] -> f [a] sequence' [] = pure [] sequence' (x:xs) = liftA2 (flip (:)) xs x The difference is that it binds the tail of the list first, so the generated tails are shared. This means less consing, less GC strain, and a lot less memory usage if you store them. Mind, the answers come out in a different order. Luke

Luke Palmer schrieb:
\begin{code} allPossibilities :: [[a]] -> [[a]] allPossibilities [] = [[]] allPossibilities (l:ls) = [ x : xs | x <- l, xs <- allPossibilities ls]
I am confused. This is exactly sequence. How is this a faster version? Other than maybe avoiding some dictionary-passing?
I suppose, dictionary-passing is really the reason for slower code.
Incidentally there is a "better" version of sequence for finding products of lists:
allPossibilities :: [[a]] -> [[a]] allPossibilities [] = [[]] allPossibilities (l:ls) = [ x : xs | xs <- allPossibilites ls, x <- l ]
I cannot really observe a speed up, with this version, but there are probably examples where any version is faster than the other.
Or, the general form (I don't know of a use other than for lists, however):
"Maybe" should be another useful instance.
sequence' :: Applicative f => [f a] -> f [a] sequence' [] = pure [] sequence' (x:xs) = liftA2 (flip (:)) xs x
The difference is that it binds the tail of the list first, so the generated tails are shared. This means less consing, less GC strain, and a lot less memory usage if you store them.
This argument it too complicated for me.
Mind, the answers come out in a different order.
Yes, thanks. Christian

Am Freitag 04 Dezember 2009 16:48:25 schrieb Christian Maeder:
Luke Palmer schrieb:
\begin{code} allPossibilities :: [[a]] -> [[a]] allPossibilities [] = [[]] allPossibilities (l:ls) = [ x : xs | x <- l, xs <- allPossibilities ls]
I am confused. This is exactly sequence. How is this a faster version? Other than maybe avoiding some dictionary-passing?
I suppose, dictionary-passing is really the reason for slower code.
I don't think so. With the code of sequence specialised to lists, I get the same performance as with Control.Monad.sequence (at least, the difference is too small to be reliably measured), while allPossibilities is significantly faster. Perhaps the code generator can handle list comprehensions better than folds?
Incidentally there is a "better" version of sequence for finding products of lists:
allPossibilities :: [[a]] -> [[a]] allPossibilities [] = [[]] allPossibilities (l:ls) = [ x : xs | xs <- allPossibilites ls, x <- l ]
I cannot really observe a speed up, with this version, but there are probably examples where any version is faster than the other.
I can, dafis@linux-mkk1:~/Haskell/CafeTesting> time ./pairs 7 9 20 5529600 0.18user 0.00system 0:00.18elapsed 102%CPU (0avgtext+0avgdata 0maxresident)k 0inputs+0outputs (0major+521minor)pagefaults 0swaps dafis@linux-mkk1:~/Haskell/CafeTesting> time ./pairs +RTS -A200M -RTS 6 9 20 5529600 0.45user 0.26system 0:00.71elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k 0inputs+0outputs (0major+56604minor)pagefaults 0swaps
Or, the general form (I don't know of a use other than for lists, however):
"Maybe" should be another useful instance.
sequence' :: Applicative f => [f a] -> f [a] sequence' [] = pure [] sequence' (x:xs) = liftA2 (flip (:)) xs x
The difference is that it binds the tail of the list first, so the generated tails are shared. This means less consing, less GC strain, and a lot less memory usage if you store them.
This argument it too complicated for me.
aP1 [] = [[]] aP1 (h:t) = do x <- h xs <- aP1 t return (x:xs) for every x in h, we calculate the combinations of t anew. aP2 [] = [[]] aP2 (h:t) = do xs <- aP2 t x <- h return (x:xs) now we first calculate the combinations of t, for each of those, we cons the elements of h to it in turn and never reuse it afterwards.
Mind, the answers come out in a different order.
Yes, thanks.
Christian

Daniel Fischer schrieb:
allPossibilities :: [[a]] -> [[a]] allPossibilities [] = [[]] allPossibilities (l:ls) = [ x : xs | xs <- allPossibilites ls, x <- l ] I cannot really observe a speed up, with this version, but there are probably examples where any version is faster than the other.
I can,
Oh yes, I can too.
aP1 [] = [[]] aP1 (h:t) = do x <- h xs <- aP1 t return (x:xs)
for every x in h, we calculate the combinations of t anew.
Do we? Isn't "aP1 t" one closure that's being evaluated only once?
aP2 [] = [[]] aP2 (h:t) = do xs <- aP2 t x <- h return (x:xs)
now we first calculate the combinations of t, for each of those, we cons the elements of h to it in turn and never reuse it afterwards.
Thanks for explaining. C.

Am Freitag 04 Dezember 2009 19:00:33 schrieb Christian Maeder:
aP1 [] = [[]] aP1 (h:t) = do x <- h xs <- aP1 t return (x:xs)
for every x in h, we calculate the combinations of t anew.
Do we? Isn't "aP1 t" one closure that's being evaluated only once?
That depends. Firstly, it depends on the optimisation level. ---------------------------------------------------------------------- module AllPossibilities where import Debug.Trace aP1 :: [[Int]] -> [[Int]] aP1 [] = [[]] aP1 l@(h:t) = trace ("aP1 " ++ show l) [x:xs | x <- h, xs <- aP1 t] aP2 :: [[Int]] -> [[Int]] aP2 [] = [[]] aP2 l@(h:t) = trace ("aP2 " ++ show l) [x:xs | xs <- aP2 t, x <- h] ---------------------------------------------------------------------- Compiled without optimisations (or interpreted): Prelude AllPossibilities> aP1 [[1,2,3],[4,5,6],[7,8,9]] aP1 [[1,2,3],[4,5,6],[7,8,9]] aP1 [[4,5,6],[7,8,9]] aP1 [[7,8,9]] [[1,4,7],[1,4,8],[1,4,9]aP1 [[7,8,9]] ,[1,5,7],[1,5,8],[1,5,9]aP1 [[7,8,9]] ,[1,6,7],[1,6,8],[1,6,9]aP1 [[4,5,6],[7,8,9]] aP1 [[7,8,9]] ,[2,4,7],[2,4,8],[2,4,9]aP1 [[7,8,9]] ,[2,5,7],[2,5,8],[2,5,9]aP1 [[7,8,9]] ,[2,6,7],[2,6,8],[2,6,9]aP1 [[4,5,6],[7,8,9]] aP1 [[7,8,9]] ,[3,4,7],[3,4,8],[3,4,9]aP1 [[7,8,9]] ,[3,5,7],[3,5,8],[3,5,9]aP1 [[7,8,9]] ,[3,6,7],[3,6,8],[3,6,9]] Prelude AllPossibilities> aP2 [[1,2,3],[4,5,6],[7,8,9]] aP2 [[1,2,3],[4,5,6],[7,8,9]] aP2 [[4,5,6],[7,8,9]] aP2 [[7,8,9]] [[1,4,7],[2,4,7],[3,4,7],[1,5,7],[2,5,7],[3,5,7],[1,6,7],[2,6,7],[3,6,7],[1,4,8],[2,4,8], [3,4,8],[1,5,8],[2,5,8],[3,5,8],[1,6,8],[2,6,8],[3,6,8],[1,4,9],[2,4,9],[3,4,9],[1,5,9], [2,5,9],[3,5,9],[1,6,9],[2,6,9],[3,6,9]] it's evaluated multiple times. Compiled with optimisation (-O or -O2), Prelude AllPossibilities> aP1 [[1,2,3],[4,5,6],[7,8,9]] aP1 [[1,2,3],[4,5,6],[7,8,9]] aP1 [[4,5,6],[7,8,9]] aP1 [[7,8,9]] [[1,4,7],[1,4,8],[1,4,9],[1,5,7],[1,5,8],[1,5,9],[1,6,7],[1,6,8],[1,6,9],[2,4,7],[2,4,8], [2,4,9],[2,5,7],[2,5,8],[2,5,9],[2,6,7],[2,6,8],[2,6,9],[3,4,7],[3,4,8],[3,4,9],[3,5,7], [3,5,8],[3,5,9],[3,6,7],[3,6,8],[3,6,9]] Prelude AllPossibilities> aP2 [[1,2,3],[4,5,6],[7,8,9]] aP2 [[1,2,3],[4,5,6],[7,8,9]] aP2 [[4,5,6],[7,8,9]] aP2 [[7,8,9]] [[1,4,7],[2,4,7],[3,4,7],[1,5,7],[2,5,7],[3,5,7],[1,6,7],[2,6,7],[3,6,7],[1,4,8],[2,4,8], [3,4,8],[1,5,8],[2,5,8],[3,5,8],[1,6,8],[2,6,8],[3,6,8],[1,4,9],[2,4,9],[3,4,9],[1,5,9], [2,5,9],[3,5,9],[1,6,9],[2,6,9],[3,6,9]] it's only evaluated once. But if we think about what happens when we have n lists of lengths l1, ..., ln, there are l2*...*ln combinations of the tail. Each of these combinations is used l1 times, once for each element of the first list. However, between two uses of a particular combination, all the other (l2*...*ln-1) combinations are used once. If l2*...*ln is large, only a tiny fraction of the combinations of the tail fit in the memory at once, so they simply can't be reused and have to be recalculated each time (theoretically, a handful could be kept in memory for reuse). On the other hand, in aP2, each combination of the tail is of course also used l1 times, but these are in direct succession, and the combination has been bound to a name for the entire scope, it's practically guaranteed to be calculated only once and garbage collected once. By the way, if the order in which the combinations are generated matters: aP1 === map reverse . aP2 . reverse
aP2 [] = [[]] aP2 (h:t) = do xs <- aP2 t x <- h return (x:xs)
now we first calculate the combinations of t, for each of those, we cons the elements of h to it in turn and never reuse it afterwards.
Thanks for explaining.
C.

Thanks again for your patience with me, your answers to this list (and the beginners list) are in general a real pleasure! Christian Daniel Fischer schrieb:
Am Freitag 04 Dezember 2009 19:00:33 schrieb Christian Maeder:
aP1 [] = [[]] aP1 (h:t) = do x <- h xs <- aP1 t return (x:xs)
for every x in h, we calculate the combinations of t anew. Do we? Isn't "aP1 t" one closure that's being evaluated only once?
That depends. Firstly, it depends on the optimisation level. ---------------------------------------------------------------------- module AllPossibilities where
import Debug.Trace
aP1 :: [[Int]] -> [[Int]] aP1 [] = [[]] aP1 l@(h:t) = trace ("aP1 " ++ show l) [x:xs | x <- h, xs <- aP1 t]
aP2 :: [[Int]] -> [[Int]] aP2 [] = [[]] aP2 l@(h:t) = trace ("aP2 " ++ show l) [x:xs | xs <- aP2 t, x <- h] ----------------------------------------------------------------------
Compiled without optimisations (or interpreted):
Prelude AllPossibilities> aP1 [[1,2,3],[4,5,6],[7,8,9]] aP1 [[1,2,3],[4,5,6],[7,8,9]] aP1 [[4,5,6],[7,8,9]] aP1 [[7,8,9]] [[1,4,7],[1,4,8],[1,4,9]aP1 [[7,8,9]] ,[1,5,7],[1,5,8],[1,5,9]aP1 [[7,8,9]] ,[1,6,7],[1,6,8],[1,6,9]aP1 [[4,5,6],[7,8,9]] aP1 [[7,8,9]] ,[2,4,7],[2,4,8],[2,4,9]aP1 [[7,8,9]] ,[2,5,7],[2,5,8],[2,5,9]aP1 [[7,8,9]] ,[2,6,7],[2,6,8],[2,6,9]aP1 [[4,5,6],[7,8,9]] aP1 [[7,8,9]] ,[3,4,7],[3,4,8],[3,4,9]aP1 [[7,8,9]] ,[3,5,7],[3,5,8],[3,5,9]aP1 [[7,8,9]] ,[3,6,7],[3,6,8],[3,6,9]] Prelude AllPossibilities> aP2 [[1,2,3],[4,5,6],[7,8,9]] aP2 [[1,2,3],[4,5,6],[7,8,9]] aP2 [[4,5,6],[7,8,9]] aP2 [[7,8,9]] [[1,4,7],[2,4,7],[3,4,7],[1,5,7],[2,5,7],[3,5,7],[1,6,7],[2,6,7],[3,6,7],[1,4,8],[2,4,8], [3,4,8],[1,5,8],[2,5,8],[3,5,8],[1,6,8],[2,6,8],[3,6,8],[1,4,9],[2,4,9],[3,4,9],[1,5,9], [2,5,9],[3,5,9],[1,6,9],[2,6,9],[3,6,9]]
it's evaluated multiple times. Compiled with optimisation (-O or -O2),
Prelude AllPossibilities> aP1 [[1,2,3],[4,5,6],[7,8,9]] aP1 [[1,2,3],[4,5,6],[7,8,9]] aP1 [[4,5,6],[7,8,9]] aP1 [[7,8,9]] [[1,4,7],[1,4,8],[1,4,9],[1,5,7],[1,5,8],[1,5,9],[1,6,7],[1,6,8],[1,6,9],[2,4,7],[2,4,8], [2,4,9],[2,5,7],[2,5,8],[2,5,9],[2,6,7],[2,6,8],[2,6,9],[3,4,7],[3,4,8],[3,4,9],[3,5,7], [3,5,8],[3,5,9],[3,6,7],[3,6,8],[3,6,9]] Prelude AllPossibilities> aP2 [[1,2,3],[4,5,6],[7,8,9]] aP2 [[1,2,3],[4,5,6],[7,8,9]] aP2 [[4,5,6],[7,8,9]] aP2 [[7,8,9]] [[1,4,7],[2,4,7],[3,4,7],[1,5,7],[2,5,7],[3,5,7],[1,6,7],[2,6,7],[3,6,7],[1,4,8],[2,4,8], [3,4,8],[1,5,8],[2,5,8],[3,5,8],[1,6,8],[2,6,8],[3,6,8],[1,4,9],[2,4,9],[3,4,9],[1,5,9], [2,5,9],[3,5,9],[1,6,9],[2,6,9],[3,6,9]]
it's only evaluated once.
It's also evaluated only once (unoptimized) if given as follows, although I would not write it that way: aP1 :: [[Int]] -> [[Int]] aP1 [] = [[]] aP1 l@(h:t) = trace ("aP1 " ++ show l) $ let r = aP1 t in [x:xs | x <- h, xs <- r]
But if we think about what happens when we have n lists of lengths l1, ..., ln, there are l2*...*ln combinations of the tail. Each of these combinations is used l1 times, once for each element of the first list. However, between two uses of a particular combination, all the other (l2*...*ln-1) combinations are used once. If l2*...*ln is large, only a tiny fraction of the combinations of the tail fit in the memory at once, so they simply can't be reused and have to be recalculated each time (theoretically, a handful could be kept in memory for reuse).
Right, memory consumption is still the problem (maybe unless everything is needed eventually).
On the other hand, in aP2, each combination of the tail is of course also used l1 times, but these are in direct succession, and the combination has been bound to a name for the entire scope, it's practically guaranteed to be calculated only once and garbage collected once.
Yes, I see that reusing and sharing one element of xs is far easier in aP2.
By the way, if the order in which the combinations are generated matters:
aP1 === map reverse . aP2 . reverse
The order does not matter for me. But it is good to see (from a second perspective) that both variants basically produce the same combinations.
aP2 [] = [[]] aP2 (h:t) = do xs <- aP2 t x <- h return (x:xs)
now we first calculate the combinations of t, for each of those, we cons the elements of h to it in turn and never reuse it afterwards. Thanks for explaining.
C.
participants (3)
-
Christian Maeder
-
Daniel Fischer
-
Luke Palmer