Richard O'Keefe <[EMAIL PROTECTED]> wrote:
Another change to the order to give us MORE sharing takes less time AND less space. The surprise is how much less time.

Interesting stuff. My students and I briefly chatted about powerset this morning and came up with the same function, but the very significant time differences you pointed out aren't something that shows up on a whiteboard, so thanks for all those timings.

The really scary thing about this example is that so much depends on the order in which the subsets are returned, which in many cases does not matter.

(I'm going a bit off main topic from Richard's (informative) post here, but hey...)

Saying something like "let's improve space performance by doing it backwards and then reversing the list", while great in ML, won't (always) cut it in Haskell. The need to preserve laziness/strictness can tie our hands.

For example, consider yet another variant of power_list:

power_list l = [] : pow [[]] l where
    pow acc []     = []
    pow acc (x:xs) = acc_x ++ pow (acc ++ acc_x) xs
       where acc_x = map (++ [x]) acc

By many standards, this version is inefficient, with plenty of appends and lots of transient space usage.

BUT, it generates the output in an order that'll accommodate infinite lists, thus we can say:

   power_list [1..]

(none of the other versions had this property -- they'd just die here)

So, the moral for optimizations is that any transformation we do to improve space performance shouldn't make our program stricter than it was before. (I think the paper by David Sands and Joergen Gustavsson that Janis Voigtlaender mentioned covers this too, but I haven't had a chance to look at it closely yet.)

    Melissa.

P.S. For fun, I'll also note that yes, it *is* possible to code a lazy-list-friendly power_list function in a way that doesn't drag saved lists around, although it doesn't run as nearly as quickly as some of the others seen.

-- Count in binary and use that to create power set
power_list xs = loop zero where
   loop n = case select xs n of
                Nothing  -> []
                Just set -> set : loop (inc n)

   select xs     []           = Just []
   select []     nat          = Nothing
   select (x:xs) (True:nat')  = select xs nat' >>= \l -> Just (x:l)
   select (x:xs) (False:nat') = select xs nat'

   zero = []
   inc []           = [True]
   inc (False:bits) = True  : bits
   inc (True :bits) = False : inc bits

No doubt this can be coded better yet...

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to