[Haskell-cafe] Mysterious fact

Max Cantor mxcantor at gmail.com
Tue Nov 2 08:58:49 EDT 2010


FYI,

I  implemented an error monad using this church-encoded either instead of the conventional either.  my thought was that since you skip the conditional at each bind call you'd get better performance.  I was quite mistaken.

Max

On Nov 2, 2010, at 6:40 AM, Jeremy Shaw wrote:

> Looks a lot like Church encoding to me:
> 
> http://en.wikipedia.org/wiki/Church_encoding
> 
> It was first discovered by the guy who invented lambda calculus :p
> 
> - jeremy
> 
> On Nov 1, 2010, at 5:28 PM, Andrew Coppin wrote:
> 
>> The other day, I accidentally came up with this:
>> 
>> {-# LANGUAGE RankNTypes #-}
>> 
>> 
>> 
>> type Either x y = forall r.
>>  (x -> r) -> (y -> r) -> r
>> 
>> left :: x -> 
>> Either
>>  x y
>> left x f g 
>> =
>>  f x
>> 
>> right :: y -> 
>> Either
>>  x y
>> right y f g 
>> =
>>  g y
>> 
>> 
>> This is one example; it seems that just about any algebraic type can be encoded this way. I presume that somebody else has thought of this before. Does it have a name?
>> 
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list