[Haskell-cafe] Re: powerSet = filterM (const [True, False]) ... is this obfuscated haskell?

2009-07-17 Thread Gleb Alexeyev

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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: powerSet = filterM (const [True, False]) ... is this obfuscated haskell?

2009-07-17 Thread 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?



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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: powerSet = filterM (const [True, False]) ... is this obfuscated haskell?

2009-07-17 Thread porges

2009/7/17 Gleb Alexeyev gleb.alex...@gmail.com:

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

signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe