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

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

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

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 rigi

[Haskell] (no subject)

2005-03-01 Thread Duncan Coutts
Gtk2Hs - A Haskell GUI library based on the Gtk+ GUI Toolkit. Version 0.9.7.1 is now available from: http://gtk2hs.sourceforge.net/ This release is only needed for Windows users. If you have version 0.9.7 working there is no need to upgrade. Source and binary packages are available for Window

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 . (fo

[Haskell] First Issue of The Monad.Reader is online.

2005-03-01 Thread Shae Matijs Erisson
The first issue of The Monad.Reader is available: http://www.haskell.org/hawiki/TheMonadReader_2fIssueOne We'd like to hear what you think: http://www.haskell.org/hawiki/TheMonadReader_2fIssueOne_2fFeedBack -- Shae Matijs Erisson - http://www.ScannedInAvian.com/ - Sockmonster once said: You could

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

[Haskell] De-typechecker: converting from a type to a term

2005-03-01 Thread oleg
This message presents polymorphic functions that derive a term for a given type -- for a class of fully polymorphic functions: proper and improper combinators. This is better understood on an example: rtest4 f g = rr (undefined::(b -> c) -> (a -> b) -> a -> c) HNil f g *HC> rtest4 (:[]) Just