
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?

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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Monday 01 November 2010 6:40:30 pm 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
Also, if you're interested in this, you can read Proofs and Types by Girard (not an easy read). In it, (I think) he notes, and probably proves, that you can encode any inductive type in System F (which is relatively close to Haskell with rank-n types) by this method (that is, it has the right types; of course it works in the untyped lambda calculus, too, but not in, say, the simply typed lambda calculus). You can also encode coinductive types: nu F = exists s. s * (s -> F s) exists s. T[s] = forall r. (forall s. T[s] -> r) -> r -- Dan

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@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

From: Max Cantor
Sent: Tue, November 2, 2010 7:58:49 AM 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.
That's surprising, I think LogicT gains significant performance from that sort of CPS conversion. Was your code like this? newtype ErrorC e a = ErrorC (runErrorC :: forall r . (e -> r) -> (a -> r) -> r) instance Monad (ErrorC e) where return x = ErrorC (\fail succeed -> succeed x) ErrorC part1 >>= f = ErrorC (\fail succeed -> part1 fail (\a -> runErrorC (f a) fail succeed)) instance MonadError e (ErrorC e) where throwError e = ErrorC (\fail succeed -> fail e) catchError m handler = ErrorC (\fail succeed -> runErrorC m (\err -> runErrorC (handler err) fail succeed) succeed) Brandon Moore

On Tue, Nov 2, 2010 at 2:11 PM, Brandon Moore
From: Max Cantor
Sent: Tue, November 2, 2010 7:58:49 AM 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.
That's surprising, I think LogicT gains significant performance from that sort of CPS conversion.
Was your code like this?
newtype ErrorC e a = ErrorC (runErrorC :: forall r . (e -> r) -> (a -> r) -> r)
instance Monad (ErrorC e) where return x = ErrorC (\fail succeed -> succeed x) ErrorC part1 >>= f = ErrorC (\fail succeed -> part1 fail (\a -> runErrorC (f a) fail succeed))
instance MonadError e (ErrorC e) where throwError e = ErrorC (\fail succeed -> fail e) catchError m handler = ErrorC (\fail succeed -> runErrorC m (\err -> runErrorC (handler err) fail succeed) succeed)
In a monad transformer, performing a CPS translation has the benefit of being able to implement bind, return and other effects without having to pass through operations on the wrapped monad. This could be part of the performance improvement you're seeing. Antoine

On Tuesday 02 November 2010 3:11:22 pm Brandon Moore wrote:
That's surprising, I think LogicT gains significant performance from that sort of CPS conversion.
It's probably not that surprising. LogicT is an encoding of a recursive type, so there's potentially more causes for the gain. For instance, if we just look at Logic versus lists, Logic has concatenation that is O(1), and associative with regard to performance. For lists, that's O(m), and you get quadratic behavior with left-nesting. That alone may account for a lot of the performance boost, since the main idea of Logic is to be used as a monad for backtracking search, which is all concatMap. Either, on the other hand, is a non-recursive data type, so I doubt you can milk any asymptotic improvements out of an encoding. Further, GHC has fancy constructor specialization optimizations developed specifically (I think) to make using these non-recursive sum types fast. For that matter, I can't say I've benchmarked Logic against lists recently. -- Dan

On 01/11/2010 10:40 PM, 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
Yes, well, the various Church encodings and the lambda calculus in general are where I got the idea. I was just wondering if there's a specific term for using this in concrete programs rather than as a theoretical exercise, that's all.

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?

Hi, Am Montag, den 01.11.2010, 22:28 +0000 schrieb Andrew Coppin:
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?
that reminds me very much of a similar sounding mail to this list by me¹. Is there a name for this meme already? :-) Greetings, Joachim ¹ http://www.mail-archive.com/haskell-cafe@haskell.org/msg21500.html -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de ICQ#: 74513189 Jabber-ID: nomeata@joachim-breitner.de

Andrew Coppin
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?
You could try reading my PhD thesis! http://www.cl.cam.ac.uk/techreports/UCAM-CL-TR-75.html contains a link to the full text scanned to a pdf. (That -- 1985 -- was a long time ago. One thing I really regret about it is that there should have been a comma between "simple" and "typed" in the title. I suspect people think "simply typed" when they see it). It isn't hard to read (one of my examiners said it made good bed-time reading). Anyway, the relevant part is that Ponder was a programming language (Stuart Wray even wrote a GUI programme in it) that had (in principle) no built-in types, relying on the type system being powerful enough to express anything and the optimiser being good enough to convert them to something more sensible. In practice neither was /quite/ true, but it got quite close. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2010-09-14)

Jon, you beat me to it. I was going to mention Ponder.
But Ponder did have a builtin type, it had the function type built in. :)
-- Lennart
On Tue, Nov 2, 2010 at 9:47 PM, Jon Fairbairn
Andrew Coppin
writes: 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?
You could try reading my PhD thesis! http://www.cl.cam.ac.uk/techreports/UCAM-CL-TR-75.html contains a link to the full text scanned to a pdf. (That -- 1985 -- was a long time ago. One thing I really regret about it is that there should have been a comma between "simple" and "typed" in the title. I suspect people think "simply typed" when they see it). It isn't hard to read (one of my examiners said it made good bed-time reading).
Anyway, the relevant part is that Ponder was a programming language (Stuart Wray even wrote a GUI programme in it) that had (in principle) no built-in types, relying on the type system being powerful enough to express anything and the optimiser being good enough to convert them to something more sensible. In practice neither was /quite/ true, but it got quite close.
-- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2010-09-14)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Lennart Augustsson
Jon, you beat me to it. I was going to mention Ponder.
Strange chance; yesterday was the first time I read haskell café for something like half a year.
But Ponder did have a builtin type, it had the function type built in. :)
Well, to use the nomenclature of Ponder itself, (->) is a type /generator/, not a type. So either it had no built-in types, or it had infinitely many ;-) -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On 11/1/10 6: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?
Depending on how you mean for it to interact with recursion there are different names. Church encoding has already been mentioned, the other big one is Scott encoding. To illustrate the difference: -- Note how the recursive site is @r@ newtype ChurchList a = CL { foldrCL :: forall r. r -> (a -> r -> r) -> r } churchNil :: forall a. ChurchList a churchNil = CL $ \n c -> n churchCons :: forall a. a -> ChurchList a -> ChurchList a churchCons x xs = CL $ \n c -> c x (foldrCL xs n c) churchFoldr :: forall a b. b -> (a->b->b) -> ChurchList a -> b churchFoldr n c xs = foldrCL xs n c -- Note how the recursive site is @ScottList a@ newtype ScottList a = SL { caseSL :: forall r. r -> (a -> ScottList a -> r) -> r } scottNil :: forall a. ScottList a scottNil = SL $ \n c -> n scottCons :: forall a. a -> ScottList a -> ScottList a scottCons x xs = SL $ \n c -> c x xs scottFoldr :: forall a b. b -> (a->b->b) -> ScottList a -> b scottFoldr n c xs = caseSL xs n (\x xs' -> c x (scottFoldr n c xs')) While the Church encodings seem to be more popular in general, Scott encodings can be seen in /Data Types and Pattern Matching by Function Application/ [1]. The authors of [1] erroneously claim that the Scott encodings cannot be typed in Haskell--- though to be fair, the use of newtypes is requisite for Scott encodings (because the type is infinite) whereas we can use a type alias for Church encodings if desired. As Wikipedia says[2], the well-typedness of Scott encodings is not nearly as straightforward as the well-typedness of Church encodings. Both require full System F (i.e., -XRankNTypes), but Scott encodings also require recursive definitions both at the type level (i.e., newtypes to box off the recursive structure of the infinite type term) and at the value level (in order to define the catamorphisms). The Church vs Scott perspectives on recursion can also be seen in the duality of build/foldr vs unfoldr/destroy list fusion, and has connections to the iterator/data pull-model vs the iteratee/enumerator push-model. Other than the specific encodings, this sort of thing is usually just called "a CPS transformation". Which isn't very informative. [1] http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.76.5557 [2] http://en.wikipedia.org/wiki/Mogensen–Scott_encoding -- Live well, ~wren

Andrew Coppin
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?
You may want to have a look at my contstuff library, which implements all the usual monads in CPS: http://hackage.haskell.org/package/contstuff This is just the style you implemented Either in, but slightly more general and with an explicit result type parameter: newtype EitherT r e m a = EitherT { getEitherT :: (a -> m r) -> (e -> m r) -> m r } Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
participants (12)
-
Andrew Coppin
-
Antoine Latter
-
Brandon Moore
-
Dan Doel
-
Ertugrul Soeylemez
-
Henning Thielemann
-
Jeremy Shaw
-
Joachim Breitner
-
Jon Fairbairn
-
Lennart Augustsson
-
Max Cantor
-
wren ng thornton