Re: [Haskell-cafe] Functional dependencies and type inference

2005-08-23 Thread Malcolm Wallace
Thomas Jäger [EMAIL PROTECTED] writes: I believe there may be some nasty interactions with generalized newtype-deriving, since we can construct two Leibniz-equal types which are mapped to different types using fundeps: class Foo a where foo :: forall f. f Int - f a instance Foo

Re: [Haskell-cafe] Functional dependencies and type inference

2005-08-22 Thread Thomas Jäger
Simon, I believe there may be some nasty interactions with generalized newtype-deriving, since we can construct two Leibniz-equal types which are mapped to different types using fundeps: class Foo a where foo :: forall f. f Int - f a instance Foo Int where foo = id newtype Bar =

RE: [Haskell-cafe] Functional dependencies and type inference

2005-08-11 Thread Simon Peyton-Jones
2005 13:48 | To: haskell-cafe@haskell.org | Subject: [Haskell-cafe] Functional dependencies and type inference | | Hello | | I am having problems with GHC infering functional dependencies related | types in a too conservative fashion. | | class Imp2 a b | a - b | instance Imp2 (Foo a) (Wrap

Re: [Haskell-cafe] Functional dependencies and type inference

2005-08-11 Thread Iavor Diatchki
Hello, On 8/11/05, Simon Peyton-Jones [EMAIL PROTECTED] wrote: ... Here is a boiled down version, much simpler to understand. module Proxy where class Dep a b | a - b instance Dep Char Bool foo :: forall a. a - (forall b. Dep a b = a - b) - Int

[Haskell-cafe] Functional dependencies and type inference

2005-07-15 Thread Einar Karttunen
Hello I am having problems with GHC infering functional dependencies related types in a too conservative fashion. class Imp2 a b | a - b instance Imp2 (Foo a) (Wrap a) newtype Wrap a = Wrap { unWrap :: a } data Foo a = Foo data Proxy (cxt :: * - *) foo :: Imp2 (ctx c) d = Proxy ctx -