Melissa O'Neill wrote:
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...

And it can. Though the speed depends on whether you use and Int or Integer to keep track of the length of the input list. (If you want a power set of a list with 2^31 elements then you can change to Integer).

Your code for power_list and mine for powerBin and powerBin2 work in infinite 
lists:

*Main> take 10 (power_list [1..])
[[],[1],[2],[1,2],[3],[1,3],[2,3],[1,2,3],[4],[1,4]]
*Main> take 10 (powerBin [1..])
[[],[1],[2],[1,2],[3],[2,3],[1,3],[1,2,3],[4],[3,4]]
*Main> take 10 (powerBin2 [1..])
[[],[1],[1,2],[2],[1,2,3],[1,3],[2,3],[3],[1,2,3,4],[1,2,4]]

Though they all disagree about the order involved.  My actual code:

powerBin [] = [[]]
powerBin xs = [] : upto (0 :: Int)
  where upto limit = fromTo limit id (upto (succ limit)) xs
where fromTo n acc cont [] = [] -- reached past end of input list, now done fromTo 0 acc cont (y:_) = (acc . (y:) $ []) : cont
                fromTo  n  acc  cont (y:ys) =
                    let n' = pred n
                        acc' = acc . (y:)
                        cont' = fromTo n' acc' cont ys
                    in fromTo n' acc cont' ys

And a version with acc' and acc switched:

powerBin2 [] = [[]]
powerBin2 xs = [] : upto (0 :: Int)
  where upto limit = fromTo limit id (upto (succ limit)) xs
where fromTo n acc cont [] = [] -- reached past end of input list, now done fromTo 0 acc cont (y:_) = (acc . (y:) $ []) : cont
                fromTo  n  acc  cont (y:ys) =
                    let n' = pred n
                        acc' = acc . (y:)
                        cont' = fromTo n' acc cont ys
                    in fromTo n' acc' cont' ys


The above never uses (++) or 'reverse' but does build a DList of (y:) for 'acc'. If you do not care if the returned lists are individually reversed then you can use List for acc with (acc' = (y:acc)).

The performance on ghc-6.6.1 with -O2 on PPC G4 applied to

main = print (length (power_list [1..22]))

real    0m8.592s
user    0m7.017s
sys     0m0.687s

main = print (length (powerBin [1..22]))

real    0m3.245s
user    0m2.768s
sys     0m0.073s

main = print (length (powerBin2 [1..22]))

real    0m3.305s
user    0m2.835s
sys     0m0.071s

--
Chris Kuklewicz

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

Reply via email to