[Haskell-cafe] Powerset of a set

Olaf Klinke olf at aatal-apotheke.de
Wed Sep 16 14:38:37 UTC 2015


Jerzy is right, of course. I should have issued the warning to Jorge: If you just want to understand how to compute the powerset, don't look into filterM. But in a way, filterM works like Jerzy's Prolog example: 

filterM (const [False,True]) [] = [[]]
-- filterM is defined via foldr with base case (return []).

filterM (const [False,True]) (x:xs) = do

  includeFirstElement <- [False,True]
  -- in reality, includeFirstElem <- const [False,True] x

  subsetOfxs <- filterM (const [False,True] xs)
  -- recursive call.

  return (if includeFirstElement then x:subsetOfxs else subsetOfxs)

In order to produce a sublist of a list, 
we need to decide for each element if we want to include it in the sublist. That is, a sublist of xs :: [a] can be obtained by running 

  filter (p :: a -> Bool) xs

for some decision procedure p. The type of filterM allows the decision procedure to give more than one answer. In our case, the p, when asked "Should we include this particular element in the sublist?" always answers "Yes and No!". 

Is there a monad transformer generalisation of filterM, where the monad [] is replaced by other monad(-transformer)s? Recall that many monad transformers rely on distributive laws. 

class Distributive t where
  distrib :: (Monad m) => t (m a) -> m (t a)
instance Distributive [] where
  distrib = sequence

The term

  \p -> liftM (\x -> liftM (\b -> if b then return x else mzero) (p x))

can be given the type 

  (Monad m, MonadPlus t) => (a -> m Bool) -> t a -> t (m (t a))

Therefore the term 

  \p -> (liftM join).distrib.(liftM (\x -> liftM (\b -> if b then return x else mzero) (p x)))

can be given the type 

  (MonadPlus t,Distributive t, Monad m) => (a -> m Bool) -> t a -> m (t a)

Indeed for t = [] it is equivalent to filterM. To explain what's going on, notice that 

  sequence :: Monad m => [m a] -> m [a] 

computes, when m = [], all possible ways of picking one element from each list in a list of lists. One could say that sequence produces choice functions. I used sequence above: To compute the powerset of a set, replace each element x by the set {{},{x}}, then compute all choices, and then take the union of each such choice. 

-- Olaf


More information about the Haskell-Cafe mailing list