[Haskell-cafe] partitions of a multiset

Brent Yorgey byorgey at gmail.com
Mon Jul 23 12:27:30 EDT 2007


Hi all,

I've written some code to generate set partitions:

import Control.Arrow
import Data.List

-- pSet' S generates the power set of S, with each subset paired
--   with its complement.
--   e.g. pSet' [1,2] = [([1,2],[]),([1],[2]),([2],[1]),([],[1,2])].
pSet' :: [a]   -> [([a],[a])]
pSet'    []     = [([],[])]
pSet'    (x:xs) = mp first ++ mp second where
    mp which = map (which (x:)) psRest
    psRest = pSet' xs

-- partitions S generates a list of partitions of S.
-- e.g. partitions [1,2,3] =
[[[1,2,3]],[[1,2],[3]],[[1,3],[2]],[[1],[2,3]],[[1],[2],[3]]].
partitions :: [a] -> [[[a]]]
partitions [] = [[]]
partitions (x:xs) = (pSet' xs) >>= ((x:) *** partitions >>> uncurry (map .
(:)))

However, this version of partitions generates duplicates when given a
multiset, for example:

*Combinatorics> partitions [1,1,2]
[[[1,1,2]],[[1,1],[2]],[[1,2],[1]],[[1],[1,2]],[[1],[1],[2]]]

The partition [[1,2],[1]] is generated twice (order doesn't matter).  I'd
like to write a version of partitions which generates duplicate-free output
even for input multisets, but haven't come up with a good method yet.  Any
ideas?

-Brent

PS Yes, this is for Project Euler. =)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070723/785e9bc9/attachment.htm


More information about the Haskell-Cafe mailing list