[Haskell-cafe] Re: Mysterious fact

2010-11-08 Thread Ertugrul Soeylemez
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?

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/


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


[Haskell-cafe] Re: Mysterious fact

2010-11-03 Thread Jon Fairbairn
Lennart Augustsson  writes:

> 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.fairba...@cl.cam.ac.uk


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


Re: [Haskell-cafe] Re: Mysterious fact

2010-11-02 Thread Lennart Augustsson
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
 wrote:
> 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!
> 
> 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.fairba...@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
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Mysterious fact

2010-11-02 Thread 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!

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