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

2005-03-01 Thread John Meacham
On Mon, Feb 28, 2005 at 11:10:40PM -0500, Jim Apple wrote: Jon Fairbairn wrote: If you allow quantification over higher kinds, you can do something like this: d f = f . f d:: a::*, b::**.(b a a) b (b a) a What's the problem with d :: (forall c . b c - c) - b (b a) - a d f

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

2005-03-01 Thread Jacques Carette
It is really too bad the 'middle' version does not work, ie John Fairbarn's version d1 :: (forall c . b c - c) - b (b a) - a d1 f = f . f John Meacham's version (dual (?)) d2 :: (forall c . c - b c) - a - b (b a) d2 f = f . f Or something in the middle d3 :: forall e a b . (forall c . e

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

2005-03-01 Thread Keean Schupke
Actually none of these seem to work: {-# OPTIONS -fglasgow-exts #-} module Main where main :: IO () main = putStrLn OK d :: (forall c . b c - c) - b (b a) - a d f = f . f t0 = d id t1 = d head t2 = d fst Load this into GHCI and you get: Test.hs:11:7: Couldn't match the rigid variable `c'

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

2005-03-01 Thread Jon Fairbairn
On 2005-02-28 at 23:10EST Jim Apple wrote: Jon Fairbairn wrote: If you allow quantification over higher kinds, you can do something like this: d f = f . f d:: a::*, b::**.(b a a) b (b a) a What's the problem with d :: (forall c . b c - c) - b (b a) - a d f = f . f

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

2005-03-01 Thread Jim Apple
Jon Fairbairn wrote: If you allow quantification over higher kinds, you can do something like this: d f = f . f d:: a::*, b::**.(b a a) b (b a) a What's the problem with d :: (forall c . b c - c) - b (b a) - a d f = f . f to which ghci gives the type d :: forall a b. (forall c. b c - c) - b

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

2005-02-28 Thread Jim Apple
Jon Fairbairn wrote: If you allow quantification over higher kinds, you can do something like this: d f = f . f d:: a::*, b::**.(b a a) b (b a) a What's the problem with d :: (forall c . b c - c) - b (b a) - a d f = f . f to which ghci gives the type d :: forall a b. (forall c. b c - c) -