RE: Data.Typeable and default instances

2005-12-05 Thread Simon Peyton-Jones
Jim

You've found a strange corner case.   Here's a cut-down example, which
fails in exactly the same way.

class Baz v x where
   foo :: x - x-- Notice that v is not mentioned
   foo y = y

instance Baz Int Int

But it succeeds if you put the instance explicitly:

instance Baz Int Int where foo y = y

GHC does not actually macro-expand the instance decl.  Instead, it
defines a default method function, thus

$dmfoo :: Baz v x = x - x
$dmfoo y = y

Notice that this is an ambiguous type: you can't call $dmfoo without
triggering an error.  And when you write an instance decl, it calls the
default method:

instance Baz Int Int where foo = $dmfoo


I'd never thought of that.  You might think that we should just *infer*
the type of the default method (here forall a. a-a), but in the
presence of higher rank types etc we can't necessarily do that.

So I'm not sure what to do.  I've added it as an expected-failure test
(tc199).  I have not added a SourceForge bug because the original
program seems so implausible.  

Meanwhile, the workaround is to define your own default method, thus:
dmfoo :: x - x
dmfoo y = y

instance Baz Int Int where foo = dmfoo

Simom



| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-users-
| [EMAIL PROTECTED] On Behalf Of Jim Apple
| Sent: 04 December 2005 17:24
| To: glasgow-haskell-users@haskell.org
| Subject: Data.Typeable and default instances
| 
|   {-# OPTIONS -fglasgow-exts #-}
|  
|   import Maybe
|   import Data.Typeable
|  
|   data Nil = Nil deriving (Eq,Typeable,Show)
|  
|   class (Typeable t) = List a t where
|   init :: (t - b) - (forall y . (List a y) = y - b)
|   init f z = fromJust $ do x - cast z
|return $ f x
|  
|   instance List a Nil where
| 
|  Could not deduce (List a1 y)
|from the context (List a Nil, Typeable Nil, List a y)
|arising from use of `Main.$dminit' at Main.hs:21:0
|  Probable fix: add (List a1 y) to the class or instance method
| `Main.init'
|  In the definition of `init': init = Main.$dminit
|  In the definition for method `Main.init'
|  In the instance declaration for `List a Nil'
| 
| but copying and pasting the code from init to the instance declaration
| works fine.
| 
| Jim
| 
| ___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Data.Typeable and default instances

2005-12-04 Thread Jim Apple

 {-# OPTIONS -fglasgow-exts #-}

 import Maybe
 import Data.Typeable

 data Nil = Nil deriving (Eq,Typeable,Show)

 class (Typeable t) = List a t where
 init :: (t - b) - (forall y . (List a y) = y - b)
 init f z = fromJust $ do x - cast z
  return $ f x

 instance List a Nil where

Could not deduce (List a1 y)
  from the context (List a Nil, Typeable Nil, List a y)
  arising from use of `Main.$dminit' at Main.hs:21:0
Probable fix: add (List a1 y) to the class or instance method 
`Main.init'

In the definition of `init': init = Main.$dminit
In the definition for method `Main.init'
In the instance declaration for `List a Nil'

but copying and pasting the code from init to the instance declaration 
works fine.


Jim

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users