[Haskell-cafe] Confusion on the third monad law when using lambda
abstractions
wren ng thornton
wren at freegeek.org
Sat Jun 20 00:03:35 EDT 2009
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
More information about the Haskell-Cafe
mailing list