[Haskell-cafe] Mysterious fact

Henning Thielemann lemming at henning-thielemann.de
Mon Nov 1 18:40:51 EDT 2010


On Mon, 1 Nov 2010, 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?

http://www.haskell.org/haskellwiki/Functions_not_data_structures

The article could be more informative. This was asked several times in 
Haskell-Cafe, thus it should certainly be Category:FAQ - but with what 
title?


More information about the Haskell-Cafe mailing list