[Haskell-cafe] Re: computing lists of pairs
Daniel Fischer
daniel.is.fischer at web.de
Fri Dec 4 14:11:12 EST 2009
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.
More information about the Haskell-Cafe
mailing list