[Haskell-cafe] powerSet = filterM (const [True, False]) and Data.List permutation

Jan Christiansen jac at informatik.uni-kiel.de
Wed Aug 5 08:03:44 EDT 2009


Hi,

i am replying to a thread called "Data.List permutations"  on ghc- 
users and a thread called "powerSet = filterM (const [True,  
False]) ... is  this obfuscated haskell?" on haskell cafe.

On 04.08.2009, at 19:48, Slavomir Kaslev wrote:

> A friend mine, new to functional programming, was entertaining  
> himself by
> writing different combinatorial algorithms in Haskell. He asked me  
> for some
> help so I sent him my quick and dirty solutions for generating  
> variations and
> permutations:


On the haskell cafe thread it was observed that you can implement the  
permutations function in a non-deterministic favour. The ideas behind  
these implementations closely resemble implementations of  
corresponding functions in Curry.

We can generalise your implementation to an arbitrary MonadPlus. The  
idea is that the MonadPlus represents non-determinism. `inter` non- 
deterministically inserts an element to every possible position of its  
argument list.

inter x [] = [[x]]
>> inter x yys@(y:ys) = [x:yys] ++ map (y:) (inter x ys)

interM :: MonadPlus m => a -> [a] -> m [a]
interM x [] = return [x]
interM x yys@(y:ys) =
  return (x:yys)
    `mplus`
  liftM (y:) (interM x ys)

>> perm [] = [[]]
>> perm (x:xs) = concatMap (inter x) (perm xs)

permM :: MonadPlus m => [a] -> m [a]
permM [] = return []
permM (x:xs) = interM x =<< permM xs

Alternatively we can implement permM by means of foldM.

permM :: MonadPlus m => [a] -> m [a]
permM = foldM (flip interM) []

A standard example for the use of non-determinism in Curry is a perm  
function that looks very similar to `permM` with the slight difference  
that you do not need the monad in Curry.


An alternative to this definition is to define a monadic version of  
insertion sort. First we define a monadic equivalent of the `insertBy`  
function as follows:

-- insertBy :: (a -> a -> Bool) -> a -> [a] -> [a]
-- insertBy _ x []     = [x]
-- insertBy le x (y:ys) =--  if le x y--     then x:y:ys
--     else y:insertBy le x ys

insertByM :: MonadPlus m => (a -> a -> m Bool) -> a -> [a] -> m [a]
insertByM _ x [] = return [x]
insertByM le x (y:ys) = do
  b <- le x y
  if b
     then return (x:y:ys)
     else liftM (y:) (insertByM le x ys)

Note that this function is very similar to interM, that is, we have

  interM = insertByM (\_ _ -> return False `mplus` return True)

On basis of `insertBy` we can define insertion sort.

-- sortBy :: (a -> a -> Bool) -> [a] -> [a]
-- sortBy le = foldr (insertBy le) []

In the same manner we can define a function `sortByM` by means of  
`insertByM`.

sortByM :: MonadPlus m => (a -> a -> m Bool) -> [a] -> m [a]
sortByM le = foldM (flip (insertByM le)) []

Now we can define a function that enumerates all permutations by means  
of `sortByM`.

permM :: MonadPlus m => [a] -> m [a]
permM = sortByM (\_ _ -> return False `mplus` return True)


Interestingly we can also define permM by means of monadic  
counterparts of other sorting algorithms like mergeSort. Although  
there were some arguments on haskell cafe that this would not work for  
other sorting algorithms it looks like this is not the case. At least  
the corresponding implementation of perm by means of mergeSort in  
Curry works well for lists that I can test in reasonable time.

Cheers, Jan


More information about the Haskell-Cafe mailing list