A brief search of the libraries didn't reveal (top me) a ready-to-roll powerset function.

I thought this may be a useful exercise to see how well I'm picking up on functional programming idioms, so I offer the following for comment:

[[
-- |Powerset of a list, in ascending order of size.
--  Assumes the supplied list has no duplicate elements.
powerSet :: [a] -> [[a]]
powerSet as =
    foldl (++) [] [ combinations n as | n <- intRange 1 (length as) ]

-- |Combinations of n elements from a list, each being returned in the
--  order that they appear in the list.
combinations :: Int -> [a] -> [[a]]
combinations _ []       = []        -- Don't include empty combinations
combinations n as@(ah:at)
    | n <= 0            = [[]]
    | n >  length as    = []
    | n == length as    = [as]
    | otherwise         = (map (ah:) $ combinations (n-1) at) ++
                          (combinations n at)

-- |Return list of integers from lo to hi.
intRange :: Int -> Int -> [Int]
intRange lo hi = take (hi-lo+1) (iterate (+1) 1)

-- Tests
testcomb0 = combinations 0 "abcd" -- []
testcomb1 = combinations 1 "abcd" -- ["a","b","c","d"]
testcomb2 = combinations 2 "abcd" -- ["ab","ac","ad","bc","bd","cd"]
testcomb3 = combinations 3 "abcd" -- ["abc","abd","acd","bcd"]
testcomb4 = combinations 4 "abcd" -- ["abcd"]
testcomb5 = combinations 5 "abcd" -- []
testpower = powerSet "abc"        -- ["a","b","c","ab","ac","bc","abc"]
]]

I think the recursive use of 'combinations' may be inefficient, and could maybe be improved by "memoizing"?

#g


------------------- Graham Klyne <[EMAIL PROTECTED]> PGP: 0FAA 69FF C083 000B A2E9 A131 01B9 1C7A DBCA CB5E

_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to