powerSet = filterM (const [True, False]) ... is this obfuscated haskell?

on haskell reddit today powerSet = filterM (const [True, False]) is said to be beautiful / mind blowing. I just don't get it. I can play with transformations until I get powerSet [] = [[]] powerSet (x:xs) = let pxs = powerSet xs in map (x:) pxs ++ pxs which is understandable to me, but no matter how long I look at the original filterM definition it just doesn't click. Is this a uniquely haskell obfu, or is there a way of reading this definition that makes sense? If anybody agrees with me, care to throw out other examples of "obfuscated haskell considered harmful"?

On Fri, Jul 17, 2009 at 1:35 AM, Thomas Hartman
on haskell reddit today
powerSet = filterM (const [True, False])
The M is the list, i.e. *nondeterminism* monad. For each element in the list, there is one return value where it appears (True), and one where it does not (False). Basically, regular filter says that for each element in the list, we need to make a choice as to whether it occurs in the result. Here we use nondeterminism to make both choices. Luke
is said to be beautiful / mind blowing. I just don't get it. I can play with transformations until I get
powerSet [] = [[]] powerSet (x:xs) = let pxs = powerSet xs in map (x:) pxs ++ pxs
which is understandable to me, but no matter how long I look at the original filterM definition it just doesn't click.
Is this a uniquely haskell obfu, or is there a way of reading this definition that makes sense?
If anybody agrees with me, care to throw out other examples of "obfuscated haskell considered harmful"? _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

For each item, we ignore what the item actually is (hence `const`), and say that we both want it (True) and don't want it (False) in the output. Since we are using the list monad we are allowed to say this, and the filter function gives us a list of lists. I think there's probably a more intuitive name for `filterM`...

The M is the list, i.e. nondeterminism monad. For each element in the list, there is one return value where it appears (True), and one where it does not (False).
This discussion made Curry [1] programmers realise the beauty of non- determinism and lead to interesting reformulations of common list functions [2]. Here are some of them translated to Haskell: inits = takeWhileM (const [True,False]) tails = dropWhileM (const [True,False]) perms = sortByM (const [True,False]) Only that Hoogle does not know any of these monadic helper functions. Cheers, Sebastian [1]: http://www.curry-language.org/ [2]: unfortunately not yet in the mailing list archive (<http://www.informatik.uni-kiel.de/~mh/curry/listarchive/
Thread title: "beautiful non-determinism")
-- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

perms = sortByM (const [True,False])
This doesn't seem right, since the comparison function is inconsistent and moreover the results will depend on the sorting algorithm chosen. Ganesh =============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ===============================================================================

On Jul 28, 2009, at 11:06 AM, Sittampalam, Ganesh wrote:
perms = sortByM (const [True,False])
This doesn't seem right, since the comparison function is inconsistent
I was also wary about this point, e.g. QuickSort depends on transitivity.
and moreover the results will depend on the sorting algorithm chosen.
Is it only that different sorting algorithms enumerate all permutations in different orders or is there a sorting algorithm, such that the above definition does not enumerate all permutations? Here is some shirt-sleeved reasoning: Every sorting algorithm :: [Int] -> [Int] that actually sorts can describe every possible permutation (if there is a permutation that cannot be realised by the sorting algorithm then there is an input list that cannot be sorted). Hence, if this sorting algorithm is `sortBy p` for some predicate p then there are possible decisions of p to produce every possible permutation. If p makes *every* decision non- deterministically then certainly the specific decisions necessary for any specific permutation are also made. Hence, perm as defined above can yield a list that contains all permutations of the input (at least once) regardless of the sorting algorithm. Where is the hitch? Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Sebastian Fischer wrote:
On Jul 28, 2009, at 11:06 AM, Sittampalam, Ganesh wrote:
perms = sortByM (const [True,False])
and moreover the results will depend on the sorting algorithm chosen.
Is it only that different sorting algorithms enumerate all permutations in different orders or is there a sorting algorithm, such that the above definition does not enumerate all permutations?
[..]
Hence, perm as defined above can yield a list that contains all permutations of the input (at least once) regardless of the sorting algorithm.
Where is the hitch?
The "at least once" bit - unless your non-determinism is based on set rather than bag semantics, it's wrong to duplicate results. Ganesh =============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ===============================================================================

On Tue, Jul 28, 2009 at 6:47 AM, Sebastian
Fischer
perms = sortByM (const [True,False]) Hence, perm as defined above can yield a list that contains all permutations of the input (at least once) regardless of the sorting algorithm.
Where is the hitch?
The algorithm might diverge when given a non-transitive comparison operator. On Spore we had a bug where a NaN got into a list of floats we were sorting and our quicksort corrupted the heap because < isn't transitive on lists with NaNs. -- ryan

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

On Tue, Jul 28, 2009 at 10:58:53AM +0200, Sebastian Fischer wrote:
tails = dropWhileM (const [True,False])
Actually this should be tails = dropWhileM (const [False, True]) -- Felipe.

Thomas Hartman wrote:
on haskell reddit today
powerSet = filterM (const [True, False])
Does it help if we inline the 'const' function and rewrite [True, False] in monadic notation as (return True `mplus` return False)? powerSet = filterM (\x -> return True `mplus` return False). You can see that 'x' is ignored, both True and False are returned, hence x is preserved in one answer and not preserved in another.

On Jul 17, 2009 1:40pm, Thomas Hartman wrote:
my question to all 3 (so far) respondants is, how does your
explanation explain that the result is the power set?
I guess you forgot to reply to the cafe. Well, to me the modified definition I posted looks like the essence of powerset, the set of all subsets. Every element x of the input list divides the powerset in 2 halves, the first one contains x, the second one doesn't. Filtering on the non-deterministic predicate (\x -> return True `mplus` return False) in the List monad does exactly that.

2009/7/17 Gleb Alexeyev
On Jul 17, 2009 1:40pm, Thomas Hartman wrote:
my question to all 3 (so far) respondants is, how does your
explanation explain that the result is the power set?
Because powerset(s) = 2^s? I was going to make some nice code but I ended up with this monster :D {-# LANGUAGE ScopedTypeVariables #-} import Control.Monad -- a more generic "if" gif p t f | p == maxBound = t | otherwise = f -- this is filterM, but with the generic if collect _ [] = return [] collect p (x:xs) = do flg <- p x ys <- collect p xs return (gif flg (x:ys) ys) -- just changed if -> gif -- list exponentiation -- first parameter is fake, just to get an 'a' expSet :: forall a b. (Bounded a, Enum a, Eq a) => a -> [b] -> [[b]] expSet _a = collect (\_-> values :: [a]) values :: (Bounded a, Enum a) => [a] values = enumFromTo minBound maxBound data Trool = Un | Deux | Trois deriving (Bounded, Enum, Eq, Show) trool = undefined :: Trool bool = undefined :: Bool powerset = expSet bool I feel dirty :P

Thomas Hartman wrote:
on haskell reddit today powerSet = filterM (const [True, False])
is said to be beautiful / mind blowing. Is this a uniquely haskell obfu, or is there a way of reading this definition that makes sense?
To me, these are more obvious: powerSet = map catMaybes . mapM ((mzero:).return.return) powerSet = map concat . mapM ((mzero:).return.return) They work by pretty much the same principle. Perhaps they seem simpler to me only because I use mapM a lot more than I use filterM. Regards, Yitz
participants (11)
-
Felipe Lessa
-
George Pollard
-
Gleb Alexeyev
-
Jan Christiansen
-
Luke Palmer
-
porges@porg.es
-
Ryan Ingram
-
Sebastian Fischer
-
Sittampalam, Ganesh
-
Thomas Hartman
-
Yitzchak Gale