Re: [Haskell] Type of y f = f . f

2005-03-01 Thread Keean Schupke
Here's a type that fits: d :: forall b a t c. (F t c b, F t a c) = t - a - b from the following code: -# OPTIONS -fglasgow-exts #-} module Main where main :: IO () main = putStrLn OK data ID = ID data HEAD = HEAD data FST = FST class F t a b | t a - b where f :: t - a - b instance F

[Haskell] Type of y f = f . f

2005-02-28 Thread Jim Apple
Is there a type we can give to y f = f . f y id y head y fst are all typeable? Jim Apple ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Type of y f = f . f

2005-02-28 Thread Pedro Vasconcelos
On Mon, 28 Feb 2005 03:50:14 -0500 Jim Apple [EMAIL PROTECTED] wrote: Is there a type we can give to y f = f . f y id y head y fst are all typeable? Using ghci: Prelude let y f = f.f Prelude :t y y :: forall c. (c - c) - c - c So it admits principal type (a-a) - a-a. From this

Re: [Haskell] Type of y f = f . f

2005-02-28 Thread Till Mossakowski
The name y suggests that you want to define the fixpoint combinator. This works as follows: Prelude let y f = f (y f) Prelude :type y y :: forall t. (t - t) - t Prelude y (\fac n - if n == 0 then 1 else n*fac(n-1)) 10 3628800 Prelude Till Pedro Vasconcelos wrote: On Mon, 28 Feb 2005 03:50:14 -0500

Re: [Haskell] Type of y f = f . f

2005-02-28 Thread Ben Rudiak-Gould
Pedro Vasconcelos wrote: Jim Apple [EMAIL PROTECTED] wrote: Is there a type we can give to y f = f . f y id y head y fst are all typeable? Using ghci: Prelude let y f = f.f Prelude :t y y :: forall c. (c - c) - c - c So it admits principal type (a-a) - a-a. From this you can see that (y

Re: [Haskell] Type of y f = f . f

2005-02-28 Thread Jon Fairbairn
On 2005-02-28 at 18:03GMT Ben Rudiak-Gould wrote: Pedro Vasconcelos wrote: Jim Apple [EMAIL PROTECTED] wrote: Is there a type we can give to y f = f . f y id y head y fst are all typeable? Using ghci: Prelude let y f = f.f Prelude :t y y :: forall c. (c - c) -

Re: [Haskell] Type of y f = f . f

2005-02-28 Thread David Menendez
Jon Fairbairn writes: On 2005-02-28 at 18:03GMT Ben Rudiak-Gould wrote: Pedro Vasconcelos wrote: Jim Apple [EMAIL PROTECTED] wrote: Is there a type we can give to y f = f . f y id y head y fst are all typeable? Using ghci: Prelude let y f = f.f