Powerset Function 1-Liner

The best way to understand filterM's for the list monad (as is in your example) is to consider the following alternative pseudo-code'ish definition of filterM

filterM :: Monad m => (a -> m Bool) -> [a] -> m [a]
filterM p [x1, x2, .... xn] = do
                  b1 <- p x1
                  b2 <- p x2
                  ...
                  bn <- p xn
                  let element_flag_pairs = zip [x1,x2...xn] [b1,b2...bn]
                  return [ x | (x, True) <- element_flag_pairs]

With this definition of filterM you can easily see why the power-set is generated in your example.

For the sake of completeness, you might be also interested in how foldM and mapM can be defined as above

mapM :: Monad m => (a -> m b) -> [a] -> m [ b ]
mapM f [x1, x2, ... xn] = do
                   y1 <- f x1
                   y2 <- f x2
                   ...
                   yn <- f xn
                   return [y1,y2,...yn]

foldM :: Monad m => (b -> a -> m b) -> b -> [ a ] -> m b
foldM _ a [] = return a
foldM f a [x1,x2,..xn] = do
               y1 <- f a x1
               y2 <- f y1 x2
               y3 <- f y2 x3
               ...
               yn <- f y_(n-1) xn
               return yn

Hope this helps!


powerset ::                                    [a] -> [[a]]  
powerset xs = filterM (\x -> [True, False])    xs
                             -------------            -----
filterM :: Monad m => (a  -> m Bool       ) -> [a] -> m [a]
-- filter  ::         (a ->    Bool       ) -> [a] ->   [a]   (just for comparison)
                             -------------            -----
                             m Bool ~ [Bool]          m ~ []

So this is filter "in" the nondeterminism (list) monad.

Normally, filter keeps only those elements in its input list for which the predicate holds.

Nondeterministically, we get all the possibilities of keeping the elements for which the nondeterministic predicate might hold, and removing those for which it might not hold. Here, it is so for any element, so we get all the possibilities of keeping, or removing, an element.

Which is a powerset.


Another example (in a different monad), building on the one in Brent Yorgey's blog post mentioned in the comments,

  >> filterM (\x-> if even x then Just True else Nothing) [2,4..8]
Just [2,4,6,8]
  >> filterM (\x-> if even x then Just True else Nothing) [2..8]
Nothing
  >> filterM (\x-> if even x then Just True else Just False) [2..8]
Just [2,4,6,8]

Let's see how this is actually achieved, with code. We'll define

filter_M :: Monad m => (a -> m Bool) -> [a] -> m [a]
filter_M p []     = return []
filter_M p (x:xs) = p x >>= (\b ->
                if b
                    then filter_M p xs >>= (return . (x:))
                    else filter_M p xs )

Writing out the list monad's definitions for return and bind (>>=) (i.e. return x = [x], xs >>= f = concatMap f xs), this becomes

filter_L :: (a -> [Bool]) -> [a] -> [[a]]
filter_L p [] = [[]]
filter_L p (x:xs) -- = (`concatMap` p x) (\b->
                  --     (if b then map (x:) else id) $ filter_L p xs )
                  -- which is semantically the same as
                  --     map (if b then (x:) else id) $ ... 
   = [ if b then x:r else r | b <- p x, r <- filter_L p xs ]

Hence,

-- powerset = filter_L    (\_ -> [True, False])
--            filter_L :: (a  -> [Bool]       ) -> [a] -> [[a]]
powerset :: [a] -> [[a]]
powerset [] = [[]]
powerset (x:xs) 
   = [ if b then x:r else r | b <- (\_ -> [True, False]) x, r <- powerset xs ]
   = [ if b then x:r else r | b <- [True, False], r <- powerset xs ]
   = map (x:) (powerset xs) ++ powerset xs    -- (1)
   -- or, with different ordering of the results:
   = [ if b then x:r else r | r <- powerset xs, b <- [True, False] ]
   = powerset xs >>= (\r-> [True,False] >>= (\b-> [x:r|b] ++ [r|not b]))
   = powerset xs >>= (\r-> [x:r,r])
   = concatMap (\r-> [x:r,r]) (powerset xs)   -- (2)
   = concat [ [x:r,r] | r <- powerset xs  ]
   = [ s | r <- powerset xs, s <- [x:r,r] ]

and we have thus derived the two usual implementations of powerset function.

The flipped order of processing is made possible by the fact that the predicate is constant (const [True, False]). Otherwise the test would be evaluated over and over again for the same input value, and we probably wouldn't want that.


let me help you about this:

  • first: you have to understand the list monad. If you remember, we have:

    do
      n  <- [1,2]  
      ch <- ['a','b']  
      return (n,ch)
    

    The result will be: [(1,'a'),(1,'b'),(2,'a'),(2,'b')]

    Because: xs >>= f = concat (map f xs) and return x = [x]

    n=1: concat (map (\ch -> return (n,ch)) ['a', 'b'])
         concat ([ [(1,'a')], [(1,'b')] ]
         [(1,'a'),(1,'b')]
    and so forth ...
    the outermost result will be:
         concat ([ [(1,'a'),(1,'b')], [(2,'a'),(2,'b')] ])
         [(1,'a'),(1,'b'),(2,'a'),(2,'b')]
    
  • second: we have the implementation of filterM:

    filterM _ []     =  return []
    filterM p (x:xs) =  do
        flg <- p x
        ys  <- filterM p xs
        return (if flg then x:ys else ys)
    

    Let do an example for you to grasp the idea easier:

    filterM (\x -> [True, False]) [1,2,3]
    p is the lambda function and (x:xs) is [1,2,3]
    

    The innermost recursion of filterM: x = 3

    do
      flg <- [True, False]
      ys  <- [ [] ]
      return (if flg then 3:ys else ys)
    

    You see the similarity, like the example above we have:

    flg=True: concat (map (\ys -> return (if flg then 3:ys else ys)) [ [] ])
              concat ([ return 3:[] ])
              concat ([ [ [3] ] ])
              [ [3] ]
    and so forth ...
    the final result: [ [3], [] ]
    

    Likewise:

    x=2:
      do
        flg <- [True, False]
        ys  <- [ [3], [] ]
        return (if flg then 2:ys else ys)
    result: [ [2,3], [2], [3], [] ]
    x=1:
      do
        flg <- [True, False]
        ys  <- [ [2,3], [2], [3], [] ]
        return (if flg then 1:ys else ys)
    result: [ [1,2,3], [1,2], [1,3], [1], [2,3], [2], [3], [] ]
    
  • theoretically: it's just chaining list monads after all:

    filterM :: (a -> m Bool) -> [a] -> m [a]
               (a -> [Bool]) -> [a] -> [ [a] ]
    

And that's all, hope you enjoy :D

Tags:

Haskell