Difference between revisions of "GHC/Stand-alone deriving declarations"

From HaskellWiki
< GHC
Jump to navigation Jump to search
Line 3: Line 3:
 
Bjorn Bringert has recently implemented "stand-alone deriving" declarations, documented briefly here [http://www.haskell.org/ghc/dist/current/docs/users_guide/type-extensions.html#stand-alone-deriving]. There are a few loose ends which I summarise here:
 
Bjorn Bringert has recently implemented "stand-alone deriving" declarations, documented briefly here [http://www.haskell.org/ghc/dist/current/docs/users_guide/type-extensions.html#stand-alone-deriving]. There are a few loose ends which I summarise here:
 
 
  +
== Syntax ==
* The current syntax is
 
  +
 
The current syntax is
 
<haskell>
 
<haskell>
 
deriving Show for T
 
deriving Show for T
 
</haskell>
 
</haskell>
: There seems to be a consensus that this would be better:
+
There seems to be a consensus that this would be better:
 
<haskell>
 
<haskell>
 
derive instance Show T
 
derive instance Show T
 
</haskell>
 
</haskell>
: so that it looks more like a regular instance declaration. Here <hask>derive</hask> is not a new keyword; it's a "special-id", distinguished by the following <hask>instance</hask> keyword. That means that <hask>derive</hask> can still be used freely as a regular varid.
+
so that it looks more like a regular instance declaration. Here <hask>derive</hask> is not a new keyword; it's a "special-id", distinguished by the following <hask>instance</hask> keyword. That means that <hask>derive</hask> can still be used freely as a regular varid.
   
  +
== Context on the declaration ==
* Because it looks like a regular instance declaration, it would arguably be reasonable to require the programmer to supply the context. It seems odd to say:
 
  +
 
Because it looks like a regular instance declaration, it would arguably be reasonable to require the programmer to supply the context. It seems odd to say:
 
<haskell>
 
<haskell>
 
derive instance Show (T a)
 
derive instance Show (T a)
 
</haskell>
 
</haskell>
: and perhaps cleaner to say
+
and perhaps cleaner to say
 
<haskell>
 
<haskell>
 
derive instance Show a => Show (T a)
 
derive instance Show a => Show (T a)
 
</haskell>
 
</haskell>
: (At the moment, the compiler figures out the appropriate context, but at some point that automation may run out of steam.)
+
(At the moment, the compiler figures out the appropriate context, but at some point that automation may run out of steam.)
   
  +
== Interaction with "newtype-deriving" ==
* GHC's "newtype deriving mechanism" (see [http://www.haskell.org/ghc/dist/current/docs/users_guide/type-extensions.html#newtype-deriving]) should obviously work in a standalone deriving setting too. But perhaps it can be generalised a little. Currently you can only say
 
  +
 
GHC's "newtype deriving mechanism" (see [http://www.haskell.org/ghc/dist/current/docs/users_guide/type-extensions.html#newtype-deriving]) should obviously work in a standalone deriving setting too. But perhaps it can be generalised a little. Currently you can only say
 
<haskell>
 
<haskell>
 
deriving C a for Foo
 
deriving C a for Foo
 
</haskell>
 
</haskell>
: (where Foo is the newtype), and get an instance for <hask>(C a Foo)</hask>. But what if you want and instance for <hask>C Foo a</hask>, where the new type is not the last parameter. You can't do that at the moment. However, even with the new instance-like syntax, it's not clear to me how to signal the type to be derived. Consider
+
(where Foo is the newtype), and get an instance for <hask>(C a Foo)</hask>. But what if you want and instance for <hask>C Foo a</hask>, where the new type is not the last parameter. You can't do that at the moment. However, even with the new instance-like syntax, it's not clear to me how to signal the type to be derived. Consider
 
<haskell>
 
<haskell>
 
newtype Foo = F Int
 
newtype Foo = F Int
Line 33: Line 39:
 
derive instance C Foo Bar
 
derive instance C Foo Bar
 
</haskell>
 
</haskell>
: Which of these thee instances do we want?
+
Which of these thee instances do we want?
 
<haskell>
 
<haskell>
 
instance C Foo Bool => C Foo Bar
 
instance C Foo Bool => C Foo Bar
Line 39: Line 45:
 
instance C Int Bool => C Foo Bar
 
instance C Int Bool => C Foo Bar
 
</haskell>
 
</haskell>
: The obvious way to signal this is to give the instance context (just as above). This is perhaps another reason for having an explicit instance context in a standalone deriving declaration.
+
The obvious way to signal this is to give the instance context (just as above). This is perhaps another reason for having an explicit instance context in a standalone deriving declaration.
   
* Incidentally, notice that the third of the alternatives in the previous bullet unwraps two newtypes simultaneously. John Meacham suggested this example:
+
Incidentally, notice that the third of the alternatives in the previous bullet unwraps two newtypes simultaneously. John Meacham suggested this example:
 
<haskell>
 
<haskell>
 
class SetLike m k where
 
class SetLike m k where
Line 52: Line 58:
 
</haskell>
 
</haskell>
   
  +
== Duplicate instances ==
* Suppose two modules, M1 and M2 both contain an identical standalone deriving declaration
 
  +
 
Suppose two modules, M1 and M2 both contain an identical standalone deriving declaration
 
<haskell>
 
<haskell>
 
derive Show T
 
derive Show T
 
</haskell>
 
</haskell>
: Then, can you import M1 and M2 into another module X and use show on values of type T, or will you get an overlapping instance error? Since both instances are derived in the very same way, their code must be identical, so arguably we can choose either. (There is some duplicated code of course.)
+
Then, can you import M1 and M2 into another module X and use show on values of type T, or will you get an overlapping instance error? Since both instances are derived in the very same way, their code must be identical, so arguably we can choose either. (There is some duplicated code of course.)

Revision as of 09:36, 1 November 2006

Stand-alone deriving declarations

Bjorn Bringert has recently implemented "stand-alone deriving" declarations, documented briefly here [1]. There are a few loose ends which I summarise here:

Syntax

The current syntax is

  deriving Show for T

There seems to be a consensus that this would be better:

  derive instance Show T

so that it looks more like a regular instance declaration. Here derive is not a new keyword; it's a "special-id", distinguished by the following instance keyword. That means that derive can still be used freely as a regular varid.

Context on the declaration

Because it looks like a regular instance declaration, it would arguably be reasonable to require the programmer to supply the context. It seems odd to say:

  derive instance Show (T a)

and perhaps cleaner to say

  derive instance Show a => Show (T a)

(At the moment, the compiler figures out the appropriate context, but at some point that automation may run out of steam.)

Interaction with "newtype-deriving"

GHC's "newtype deriving mechanism" (see [2]) should obviously work in a standalone deriving setting too. But perhaps it can be generalised a little. Currently you can only say

  deriving C a for Foo

(where Foo is the newtype), and get an instance for (C a Foo). But what if you want and instance for C Foo a, where the new type is not the last parameter. You can't do that at the moment. However, even with the new instance-like syntax, it's not clear to me how to signal the type to be derived. Consider

  newtype Foo = F Int
  newtype Bar = B Bool
  derive instance C Foo Bar

Which of these thee instances do we want?

  instance C Foo Bool => C Foo Bar
  instance C Int Bar  => C Foo Bar
  instance C Int Bool => C Foo Bar

The obvious way to signal this is to give the instance context (just as above). This is perhaps another reason for having an explicit instance context in a standalone deriving declaration.

Incidentally, notice that the third of the alternatives in the previous bullet unwraps two newtypes simultaneously. John Meacham suggested this example:

  class SetLike m k  where 
  instance SetLike IntSet Int where
   
  newtype Id = Id Int
  newtype IdSet = IdSet IntSet
 
  derive instance SetLike IntSet Int => SetLike IdSet Id

Duplicate instances

Suppose two modules, M1 and M2 both contain an identical standalone deriving declaration

  derive Show T

Then, can you import M1 and M2 into another module X and use show on values of type T, or will you get an overlapping instance error? Since both instances are derived in the very same way, their code must be identical, so arguably we can choose either. (There is some duplicated code of course.)