[Haskell-cafe] MultiParamTypeClasses, FunctionalDependencies and FlexibleInstances using GHCi

2010-05-14 Thread Julian Fleischer
Hello,

i'm playin' around with GHCs Haskell and some extensions. I'm already aware of 
that functional dependencies are very very tricky, but there is something I 
don't understand about there implementation in GHC. I've constructed my own 
TypeClass Num providing a signature for (+), having multiple params a, b and 
c. I'm than declaring a (flexible) Instance for Prelude.Num, simply using 
(Prelude.+) for the definition of my (+) - and it does not work as I expect it 
to.

First, this is the code:
 {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, 
 TypeSynonymInstances, FlexibleInstances #-}
 import qualified Prelude
 
 class Num a b c | a b - c where
   (+) :: a - b - c
 
 instance (Prelude.Num x) = Num x x x where
   (+) = (Prelude.+)

now if I load it into GHCi and type 3 + 4 i get a whole bunch of 
error-messages.

I do understand that
 (3::Prelude.Int) + (4::Prelude.Int)
works, since I've explicitly declared 3 and 4 to be Prelude.Int and there is a 
functional dependency stating that (+) :: a b determines the results type c, by 
the Instance declaration cleary c will be the same as a and b.

Now, if I type
 3 + 4
it does not work, and i really don't understand why. If i ask GHCi for 3's type 
($ :t 3) it will answer 3 :: (Prelude.Num t) = t. But, if 3 and 4 are 
Prelude.Nums and there is an instanfe Num x x x for x of Prelude.Num - than why 
can't GHC deduce from the definitions that 3 and 4, both Prelude.Nums, can be 
used with (+) since there is an instance for Prelude.Num and my class Num - and 
the result will of course be something of Prelude.Num?

best regards,
Julian

smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] MultiParamTypeClasses, FunctionalDependencies and FlexibleInstances using GHCi

2010-05-14 Thread Jochem Berndsen

Julian Fleischer wrote:

Hello,

i'm playin' around with GHCs Haskell and some extensions. I'm already aware of that functional 
dependencies are very very tricky, but there is something I don't understand about 
there implementation in GHC. I've constructed my own TypeClass Num providing a 
signature for (+), having multiple params a, b and c. I'm than declaring a (flexible) Instance for 
Prelude.Num, simply using (Prelude.+) for the definition of my (+) - and it does not work as I 
expect it to.

First, this is the code:

{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, 
TypeSynonymInstances, FlexibleInstances #-}
import qualified Prelude

class Num a b c | a b - c where
(+) :: a - b - c

instance (Prelude.Num x) = Num x x x where
(+) = (Prelude.+)


now if I load it into GHCi and type 3 + 4 i get a whole bunch of 
error-messages.

I do understand that

(3::Prelude.Int) + (4::Prelude.Int)

works, since I've explicitly declared 3 and 4 to be Prelude.Int and there is a 
functional dependency stating that (+) :: a b determines the results type c, by 
the Instance declaration cleary c will be the same as a and b.

Now, if I type

3 + 4

it does not work, and i really don't understand why. If i ask GHCi for 3's type ($ :t 3) it 
will answer 3 :: (Prelude.Num t) = t. But, if 3 and 4 are Prelude.Nums and 
there is an instanfe Num x x x for x of Prelude.Num - than why can't GHC deduce from the 
definitions that 3 and 4, both Prelude.Nums, can be used with (+) since there is an instance 
for Prelude.Num and my class Num - and the result will of course be something of Prelude.Num?


My guess would be, that while 3 and 4 are both of a type instantiating 
Prelude.Num (your terminology are Prelude.Nums is quite confusing -- 
Prelude.Num is not a type but a type class), they need not be of the 
same type (e.g., 3 could be of type Integer, and 4 of type Double).


Jochem

--
Jochem Berndsen | joc...@functor.nl
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] MultiParamTypeClasses, FunctionalDependencies and FlexibleInstances using GHCi

2010-05-14 Thread Bulat Ziganshin
Hello Julian,

Friday, May 14, 2010, 4:18:42 PM, you wrote:

 Now, if I type
 3 + 4
 it does not work, and i really don't understand why. If i ask GHCi
 for 3's type ($ :t 3) it will answer 3 :: (Prelude.Num t) = t.
 But, if 3 and 4 are Prelude.Nums and there is an instanfe Num x x x
 for x of Prelude.Num - than why can't GHC deduce from the
 definitions that 3 and 4, both Prelude.Nums, can be used with (+)
 since there is an instance for Prelude.Num and my class Num - and
 the result will of course be something of Prelude.Num?

because 3 and 4 may have different types. Num is a class, Int is a
concrete type. 3 without additional type signature is polymorphic
value. usually type inference deduce types of numeric constants (that
all are polymorphic) from context but in your case it's impossible

your functional dependency allows to fix result type once parameter
types are known, but not other way

you appeal to *instance* definition but haskell/ghc type inference
can't use instance heads to deduce types since classes are open and
anyone can add later code that breaks your assumption (imagine that
ghc generates code for your module and later this module is imported by
someone else and additional instances are provided)

btw, quite popular problem, it arrives here each month or so :)

there are some ghc pragmas that somewhat break this rule, you may try
allow-indecidable-insances or so. but it's dangerous way


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] MultiParamTypeClasses, FunctionalDependencies and FlexibleInstances using GHCi

2010-05-14 Thread Stephen Tetley
Hi Julian

Variations of this one come up quite often, in a nutshell the
typechecker doesn't use the instance context in the way you are
expecting:

 instance (Prelude.Num x) = Num x x x where
   ^^^
   instance context

GHC takes less notice of the context than you might expect. Quite how
much notice it takes I'm finding had to establish from section 7.6 of
the user guide (Section 7.6.3.4. - Overlapping instances - appears to
indicate it might even take none, though maybe my reading is missing
something). Hopefully someone else will provide a definitive answer
soon.


http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/type-class-extensions.html

Best wishes

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


Re: [Haskell-cafe] MultiParamTypeClasses, FunctionalDependencies and FlexibleInstances using GHCi

2010-05-14 Thread Daniel Fischer
On Friday 14 May 2010 15:32:10, Bulat Ziganshin wrote:
 Hello Julian,

 Friday, May 14, 2010, 4:18:42 PM, you wrote:
  Now, if I type
 
  3 + 4
 
  it does not work, and i really don't understand why. If i ask GHCi
  for 3's type ($ :t 3) it will answer 3 :: (Prelude.Num t) = t.
  But, if 3 and 4 are Prelude.Nums and there is an instanfe Num x x x
  for x of Prelude.Num - than why can't GHC deduce from the
  definitions that 3 and 4, both Prelude.Nums, can be used with (+)
  since there is an instance for Prelude.Num and my class Num - and
  the result will of course be something of Prelude.Num?

 because 3 and 4 may have different types. Num is a class, Int is a
 concrete type. 3 without additional type signature is polymorphic
 value. usually type inference deduce types of numeric constants (that
 all are polymorphic) from context but in your case it's impossible

 your functional dependency allows to fix result type once parameter
 types are known, but not other way

 you appeal to *instance* definition but haskell/ghc type inference
 can't use instance heads to deduce types since classes are open and
 anyone can add later code that breaks your assumption (imagine that
 ghc generates code for your module and later this module is imported by
 someone else and additional instances are provided)

Exactly.


instance (Prelude.Num x) = Num x Prelude.Integer x where
a + b = a Prelude.* Prelude.fromInteger b

*Main 3 + (4 :: Prelude.Integer) :: Prelude.Double
12.0
*Main 3 + (4 :: Prelude.Integer) :: Prelude.Integer

interactive:1:0:
Overlapping instances for Num
Prelude.Integer Prelude.Integer 
Prelude.Integer
  arising from a use of `+' at interactive:1:0-25
Matching instances:
  instance (Prelude.Num x) = Num x x x
-- Defined at NClass.hs:7:9-36
  instance (Prelude.Num x) = Num x Prelude.Integer x
-- Defined at NClass.hs:10:9-50
In the expression: 3 + (4 :: Prelude.Integer) :: Prelude.Integer
In the definition of `it':
it = 3 + (4 :: Prelude.Integer) :: Prelude.Integer


 btw, quite popular problem, it arrives here each month or so :)

 there are some ghc pragmas that somewhat break this rule, you may try
 allow-indecidable-insances or so. but it's dangerous way

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


Re: [Haskell-cafe] MultiParamTypeClasses, FunctionalDependencies and FlexibleInstances using GHCi

2010-05-14 Thread Reid Barton
On Fri, May 14, 2010 at 02:18:42PM +0200, Julian Fleischer wrote:
 Hello,
 
 i'm playin' around with GHCs Haskell and some extensions. I'm already aware 
 of that functional dependencies are very very tricky, but there is 
 something I don't understand about there implementation in GHC. I've 
 constructed my own TypeClass Num providing a signature for (+), having 
 multiple params a, b and c. I'm than declaring a (flexible) Instance for 
 Prelude.Num, simply using (Prelude.+) for the definition of my (+) - and it 
 does not work as I expect it to.
 
 First, this is the code:
  {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, 
  TypeSynonymInstances, FlexibleInstances #-}
  import qualified Prelude
  
  class Num a b c | a b - c where
  (+) :: a - b - c
  
  instance (Prelude.Num x) = Num x x x where
  (+) = (Prelude.+)
 
 now if I load it into GHCi and type 3 + 4 i get a whole bunch of 
 error-messages.
 
 I do understand that
  (3::Prelude.Int) + (4::Prelude.Int)
 works, since I've explicitly declared 3 and 4 to be Prelude.Int and there is 
 a functional dependency stating that (+) :: a b determines the results type 
 c, by the Instance declaration cleary c will be the same as a and b.
 
 Now, if I type
  3 + 4
 it does not work, and i really don't understand why. If i ask GHCi for 3's 
 type ($ :t 3) it will answer 3 :: (Prelude.Num t) = t. But, if 3 and 4 are 
 Prelude.Nums and there is an instanfe Num x x x for x of Prelude.Num - than 
 why can't GHC deduce from the definitions that 3 and 4, both Prelude.Nums, 
 can be used with (+) since there is an instance for Prelude.Num and my class 
 Num - and the result will of course be something of Prelude.Num?

The reason 3 + 4 works in GHCi ordinarily but not with your
redefined (+) has to do with the rules for type-defaulting.  In the
ordinary case, GHCi is really evaluating show (3 + 4), which has a
type like (Num a, Show a) = String.  We still have a free type
variable a, and the resulting value depends on our choice for this
type (consider Integer vs. Double).  In this situation, there are
rules (Haskell '98 Report section 4.3.4) for making this choice, but
they only apply in very specific situations: in particular all of the
relevant classes (here Num and Show) must be among those defined in
the standard library.  You can demonstrate that type-defaulting is at
work by trying to load the following into GHCi:

 default ()
 x = show (3 + 4)-- error: Ambiguous type variable

(GHCi actually has slighly relaxed defaulting rules, see [1], and it
seems to be impossible to turn off defaulting within GHCi, which is
why the expression show (3 + 4) must be in a module for this
demonstration.)

There is no provision for extending the defaulting mechanism to your
own type classes.  Arguably this is a good thing, since defaulting can
sometimes behave surprisingly already under GHCi's rules, as anyone
who's run QuickCheck on a test with a type variable instantiated to ()
can attest to.

[1]: 
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/interactive-evaluation.html#extended-default-rules

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