Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-17 Thread Dan Piponi
On Wed, Jun 17, 2009 at 6:08 PM, Jon Strait wrote:
> ...but if there
> were another monad defined like,
>
> data MadMaybe a = Nothing | Perhaps | Just a

MadMaybe violates the second law. It's quite unlike a monad.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-17 Thread Jake McArthur

Jon Strait wrote:

I'm reading the third (bind associativity) law for monads in this form:

m >>= (\x -> k x >>= h)  =  (m >>= k) >>= h


Arguably, that law would be better stated as:

(h <=< k) <=< m  =  h <=< (k <=< m)

This wouldn't be so unintuitive.

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


Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-17 Thread David Menendez
On Wed, Jun 17, 2009 at 9:08 PM, Jon Strait wrote:
> I use and love Haskell, but I just have this nagging concern, that maybe
> someone can help me reason about.  If I'm missing something completely
> obvious here and making the wrong assumptions, please be gentle.  :)
>
> I'm reading the third (bind associativity) law for monads in this form:
>
> m >>= (\x -> k x >>= h)  =  (m >>= k) >>= h
>
> Now considering the definition of liftM2:
>
> liftM2 f m1 m2 = m1 >>= (\x1 -> m2 >>= (\x2 -> return (f x1 x2)))
>
> Isn't this liftM2  definition in the same form as the LHS of the third law
> equation, with (\x2 -> return (f x1 x2)) being the h function?

The usual convention here is that m, k, and h are variables bound
outside the scope of the law. In other words, the law only applies to
expressions which can be rewritten to have the form

let m = ...
k = ...
h = ...
in m >>= (\x -> k x >>= h)

In the case of liftM2, you'd have to rewrite it as,

liftM2 f m1 m2 = m >>= \x -> k x >>= h
where
m = m1
k = \x -> m2 >>= \y -> return (x,y)
h = \(x,y) -> return (f x y)

which is awkward, but works perfectly fine with the third law.

-- 
Dave Menendez 

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


Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-18 Thread Hans van Thiel

On Wed, 2009-06-17 at 21:26 -0500, Jake McArthur wrote:
> Jon Strait wrote:
> > I'm reading the third (bind associativity) law for monads in this form:
> > 
> > m >>= (\x -> k x >>= h)  =  (m >>= k) >>= h
> 
> Arguably, that law would be better stated as:
> 
>  (h <=< k) <=< m  =  h <=< (k <=< m)
> 
> This wouldn't be so unintuitive.
Hi, 
The only place I've ever seen Kleisli composition, or its flip, used is
in demonstrating the monad laws. Yet it is so elegant and, even having
its own name, it must have some practical use. Do you, or anybody else,
have some pointers?

Best Regards,

Hans van Thiel
> 
> - Jake
> 

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


Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-18 Thread Jake McArthur

Hans van Thiel wrote:

The only place I've ever seen Kleisli composition, or its flip, used is
in demonstrating the monad laws. Yet it is so elegant and, even having
its own name, it must have some practical use. Do you, or anybody else,
have some pointers?


I only just started finding places to use it myself, admittedly, but I 
now think it has common use and it fairly easy to spot. I'll take it 
slow, if not for you, as you seem to have a grasp on what these 
operators are already, then for other readers. Consider a function of 
this form:


foo x = a $ b $ c $ d $ e $ f x

The obvious thing to do here is to simply drop the `x` from both sides 
by using `(.)` instead of `($)`:


==>

foo x = a . b . c . d . e . f $ x

==>

foo = a . b . c . d . e . f

Now, consider this:

bar x = a =<< b =<< c =<< d =<< e =<< f x

If you compare that to the original version of `foo` above, you see that 
it is similar. In fact, looking at the types for `($)` and `(=<<)`:


($)   ::(a ->   b) -> (  a ->   b)
(=<<) :: Monad m => (a -> m b) -> (m a -> m b)

So, `(=<<)` is just like `($)` except for the information carried along 
by the monad.


Anyway, the "obvious" thing to do is to drop the `x` from both sides of 
the definition for `bar`. To do that with `foo` earlier, we had to 
substitute `($)` with `(.)`. What we are looking for is an equivalent 
operator for monads:


(.)   ::(b  c) -> (a ->   b) -> (a ->   c)
(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c)

So we now can do this:

==>

bar x = a <=< b <=< c <=< d <=< e <=< f $ x

==>

bar = a <=< b <=< c <=< d <=< e <=< f

And we're done.

Generally, you can transform anything of the form:

baz x1 = a =<< b =<< ... =<< z x1

into:

baz = a <=< b <=< ... <=< z

If you aren't already using `(=<<)` much more than `(>>=)` or 
do-notation then you will have a harder time finding opportunities to 
use `(<=<)` because only `(=<<)` has the same flow as function 
application, which allows your mind to play the appropriate association 
games. I suppose you could also replace `(>>=)` with `(>>>)`, but this 
would likely require more mental adjustment than replacing `(=<<)` with 
`(<=<)`.


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


Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-18 Thread Sjoerd Visscher

I had seen it before, and a bit of Googling turned up this:

  The monad laws can be written as
  return >=> g == g
  g >=> return == g
  (g >=> h) >=> k == g>=> (h >=> k)

  So, functions of type a -> m b are the arrows of a category with  
(>=>) as composition,

  and return as identity.

  http://sites.google.com/site/haskell/category-theory/thekleislicategory

Although I think I saw them somewhere else.

Sjoerd

On Jun 18, 2009, at 1:23 PM, Hans van Thiel wrote:



On Wed, 2009-06-17 at 21:26 -0500, Jake McArthur wrote:

Jon Strait wrote:
I'm reading the third (bind associativity) law for monads in this  
form:


m >>= (\x -> k x >>= h)  =  (m >>= k) >>= h


Arguably, that law would be better stated as:

(h <=< k) <=< m  =  h <=< (k <=< m)

This wouldn't be so unintuitive.

Hi,
The only place I've ever seen Kleisli composition, or its flip, used  
is

in demonstrating the monad laws. Yet it is so elegant and, even having
its own name, it must have some practical use. Do you, or anybody  
else,

have some pointers?

Best Regards,

Hans van Thiel


- Jake



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


--
Sjoerd Visscher
sjo...@w3future.com



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


Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-18 Thread Jake McArthur

Jake McArthur wrote:

Generally, you can transform anything of the form:

baz x1 = a =<< b =<< ... =<< z x1

into:

baz = a <=< b <=< ... <=< z


I was just looking through the source for the recently announced Hyena 
library and decided to give a more concrete example from a real-world 
project. Consider this function from the project's Data.Enumerator 
module[1]:


compose enum1 enum2 f initSeed = enum1 f1 (Right initSeed) >>= k
where
  f1 (Right seed) bs = ...
  k (Right seed) = ...

First, I would flip the `(>>=)` into a `(=<<)` (and I will ignore the 
`where` portion of the function from now on):


compose enum1 enum2 f initSeed = k =<< enum1 f1 (Right initSeed)

Next, transform the `(=<<)` into a `(<=<)`:

compose enum1 enum2 f initSeed = k <=< enum1 f1 $ Right initSeed

We can "move" the `($)` to the right by using `(.)`:

compose enum1 enum2 f initSeed = k <=< enum1 f1 . Right $ initSeed

Finally, we can drop the `initSeed` from both sides:

compose enum1 enum2 f = k <=< enum1 f1 . Right

I didn't test that my transformation preserved the semantics of the 
function or even that the type is still the same, but even if it's wrong 
it should give you the idea.


- Jake

[1] 
http://github.com/tibbe/hyena/blob/9655e9e6473af1e069d22d3ee75537ad3b88a732/Data/Enumerator.hs#L117

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


Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-18 Thread Colin Adams
What is enum2 doing in all of this - it appears to be ignored.

2009/6/18 Jake McArthur :
> Jake McArthur wrote:
>>
>> Generally, you can transform anything of the form:
>>
>>    baz x1 = a =<< b =<< ... =<< z x1
>>
>> into:
>>
>>    baz = a <=< b <=< ... <=< z
>
> I was just looking through the source for the recently announced Hyena
> library and decided to give a more concrete example from a real-world
> project. Consider this function from the project's Data.Enumerator
> module[1]:
>
>    compose enum1 enum2 f initSeed = enum1 f1 (Right initSeed) >>= k
>        where
>          f1 (Right seed) bs = ...
>          k (Right seed) = ...
>
> First, I would flip the `(>>=)` into a `(=<<)` (and I will ignore the
> `where` portion of the function from now on):
>
>    compose enum1 enum2 f initSeed = k =<< enum1 f1 (Right initSeed)
>
> Next, transform the `(=<<)` into a `(<=<)`:
>
>    compose enum1 enum2 f initSeed = k <=< enum1 f1 $ Right initSeed
>
> We can "move" the `($)` to the right by using `(.)`:
>
>    compose enum1 enum2 f initSeed = k <=< enum1 f1 . Right $ initSeed
>
> Finally, we can drop the `initSeed` from both sides:
>
>    compose enum1 enum2 f = k <=< enum1 f1 . Right
>
> I didn't test that my transformation preserved the semantics of the function
> or even that the type is still the same, but even if it's wrong it should
> give you the idea.
>
> - Jake
>
> [1]
> http://github.com/tibbe/hyena/blob/9655e9e6473af1e069d22d3ee75537ad3b88a732/Data/Enumerator.hs#L117
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-18 Thread Neil Brown
Clicking on the source code link reveals that enum2 is used in the where 
clause.  It's not important to the transformation that Jake was performing.


In essence, <=< is the monadic version of . (function composition) and 
as explained, it can be used to do some pointfree-like programming in 
the presence of monads.  It's also handy in the arguments to things like 
mapM.  E.g.


f = mapM (\x -> foo x >>= bar)

becomes:

f = mapM (bar <=< foo)

Neil.

Colin Adams wrote:

What is enum2 doing in all of this - it appears to be ignored.

2009/6/18 Jake McArthur :
  

Jake McArthur wrote:


Generally, you can transform anything of the form:

   baz x1 = a =<< b =<< ... =<< z x1

into:

   baz = a <=< b <=< ... <=< z
  

I was just looking through the source for the recently announced Hyena
library and decided to give a more concrete example from a real-world
project. Consider this function from the project's Data.Enumerator
module[1]:

   compose enum1 enum2 f initSeed = enum1 f1 (Right initSeed) >>= k
   where
 f1 (Right seed) bs = ...
 k (Right seed) = ...

First, I would flip the `(>>=)` into a `(=<<)` (and I will ignore the
`where` portion of the function from now on):

   compose enum1 enum2 f initSeed = k =<< enum1 f1 (Right initSeed)

Next, transform the `(=<<)` into a `(<=<)`:

   compose enum1 enum2 f initSeed = k <=< enum1 f1 $ Right initSeed

We can "move" the `($)` to the right by using `(.)`:

   compose enum1 enum2 f initSeed = k <=< enum1 f1 . Right $ initSeed

Finally, we can drop the `initSeed` from both sides:

   compose enum1 enum2 f = k <=< enum1 f1 . Right

I didn't test that my transformation preserved the semantics of the function
or even that the type is still the same, but even if it's wrong it should
give you the idea.

- Jake

[1]
http://github.com/tibbe/hyena/blob/9655e9e6473af1e069d22d3ee75537ad3b88a732/Data/Enumerator.hs#L117
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



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


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


Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-18 Thread Hans van Thiel

On Thu, 2009-06-18 at 08:34 -0500, Jake McArthur wrote:
[snip]
> So, `(=<<)` is just like `($)` except for the information carried along 
> by the monad.
> 
> Anyway, the "obvious" thing to do is to drop the `x` from both sides of 
> the definition for `bar`. To do that with `foo` earlier, we had to 
> substitute `($)` with `(.)`. What we are looking for is an equivalent 
> operator for monads:
> 
>  (.)   ::(b  c) -> (a ->   b) -> (a ->   c)
Just to show I'm paying attention, there's an arrow missing, right?
   (.)   ::(b  ->  c) -> (a ->   b) -> (a ->   c)

Many thanks, also to the others who've replied. I've wondered about
(=<<) usage for a long time too, and this is all very illuminating. I'll
work this through and put it in my monad tutorial, if I may (without
implicating you guys in any way, of course, unless you insist...)

Regards,

Hans van Thiel
[snip]

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


Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-18 Thread Jake McArthur

Hans van Thiel wrote:

Just to show I'm paying attention, there's an arrow missing, right?
   (.)   ::(b  ->  c) -> (a ->   b) -> (a ->   c)


Correct. I noticed that after I sent it but I figured that it would be 
noticed.


I also used (>>>) where I meant (>=>) at the bottom. They are 
semantically the same, of course, but (>>>) requires the Kleisli newtype. :(



Many thanks, also to the others who've replied. I've wondered about
(=<<) usage for a long time too, and this is all very illuminating. I'll
work this through and put it in my monad tutorial, if I may (without
implicating you guys in any way, of course, unless you insist...)


You're welcome. I do not insist on anything either way. ;)

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


Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-19 Thread wren ng thornton

Hans van Thiel wrote:

On Wed, 2009-06-17 at 21:26 -0500, Jake McArthur wrote:

Jon Strait wrote:

I'm reading the third (bind associativity) law for monads in this form:

m >>= (\x -> k x >>= h)  =  (m >>= k) >>= h

Arguably, that law would be better stated as:

 (h <=< k) <=< m  =  h <=< (k <=< m)

This wouldn't be so unintuitive.
Hi, 
The only place I've ever seen Kleisli composition, or its flip, used is

in demonstrating the monad laws. Yet it is so elegant and, even having
its own name, it must have some practical use. Do you, or anybody else,
have some pointers?


import Prelude hiding   (mapM)
import Data.Traversable (mapM)
import Control.Monad((<=<))
newtype Fix f = Fix { unFix :: f (Fix f) }


cata  phi  = phi   .   fmap (cata  phi)  . unFix

cataM phiM = phiM <=< (mapM (cataM phiM) . unFix)


ana   psi  =Fix . fmap (ana  psi).  psi

anaM  psiM = (liftM Fix . mapM (anaM psiM)) <=< psiM


etc. It's great for anyone who enjoys point-free style but wants to work 
with monads.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe