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

From HaskellWiki
< GHC
Jump to navigation Jump to search
Line 1: Line 1:
 
[[Category:GHC|Stand-alone deriving declarations]]
 
[[Category:GHC|Stand-alone deriving declarations]]
  +
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:
 
  +
== Standalone deriving ==
  +
 
GHC supports so-called "stand-alone deriving" declarations, which are described in the [http://www.haskell.org/ghc/dist/latest/docs/users_guide/type-extensions.html#stand-alone-deriving user manual section].
  +
  +
This page mentions points that may not be immediately obvious from the manual.
 
 
  +
== Deriving data types with non-standard contexts ==
== Syntax ==
 
   
  +
In Haskell 98, and GHC, you can't say this
The current syntax is
 
 
<haskell>
 
<haskell>
  +
data T m = MkT (m Int) deriving Eq
deriving instance Show T
 
 
</haskell>
 
</haskell>
  +
because the instance declaration would have a non-standard context. It would have to look like this:
 
== 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:
 
 
<haskell>
 
<haskell>
derive instance Show (T a)
+
instance Eq (m Int) => Eq (T m) where ...
 
</haskell>
 
</haskell>
  +
Of course, you can write the instance manually, but then you have to write
and perhaps cleaner to say
 
  +
all that tiresome code for equality. Standalone deriving lets you supply the context yourself, but have GHC write the code:
 
<haskell>
 
<haskell>
derive instance Show a => Show (T a)
+
data T m = MkT (m Int)
</haskell>
 
(At the moment, the compiler figures out the appropriate context, but at some point that automation may run out of steam.)
 
   
 
deriving instance Eq (m Int) => Eq (T m)
== Alternative Syntax ==
 
Alternatively the syntax could be:
 
<haskell>
 
instance Show a => Show (T a) derived
 
 
</haskell>
 
</haskell>
  +
Of course, you'll need to add the flags <hask>-XFlexibleContexts</hask> and <hask>-XUndecideableInstances</hask> to allow this instance declaration, but that's fair enough.
which has the advantage that the most important thing, namely the fact we are introducing an instance, is first, and the particular way we are introducing it (by deriving instead of explicitly by a <hask>where</hask> clause or using class defaults only) is second. (Another advantage is that the reserved id <hask>derived</hask> is now inside the <hask>instance</hask> construct not before it which is in line with the way other reserved ids are used in Haskell 98.)
 
   
  +
The same applies to data type declarations involving type functions.
There was a suggestion to allow just
 
  +
<haskell>
 
  +
== Variations (not implemented) ==
instance Show a => Show (T a)
 
  +
</haskell>
 
  +
This section collects some un-implemented ideas.
where the fact that the compiler is automatically deriving the content of the instance declaration is implicit in the absence of a <hask>where</hask> clause. The rationale was that the
 
<hask>where</hask> clause is already optional - if a class does not have a body then we can instead say that all instances of it are derived. However this is to misunderstand the current meaning of a missing <hask>where</hask> clause. In Haskell'98 it means that all the methods of the class are ''undefined'' for this instance (except for defaults). That is the opposite meaning to this proposal, which would say that all methods are fully defined.
 
   
== Interaction with "newtype-deriving" ==
+
=== 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
Line 66: Line 63:
 
</haskell>
 
</haskell>
   
== Duplicate instances ==
+
=== 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

Revision as of 17:02, 8 December 2008


Standalone deriving

GHC supports so-called "stand-alone deriving" declarations, which are described in the user manual section.

This page mentions points that may not be immediately obvious from the manual.

Deriving data types with non-standard contexts

In Haskell 98, and GHC, you can't say this

  data T m = MkT (m Int) deriving Eq

because the instance declaration would have a non-standard context. It would have to look like this:

  instance Eq (m Int) => Eq (T m) where ...

Of course, you can write the instance manually, but then you have to write all that tiresome code for equality. Standalone deriving lets you supply the context yourself, but have GHC write the code:

  data T m = MkT (m Int)

  deriving instance Eq (m Int) => Eq (T m)

Of course, you'll need to add the flags -XFlexibleContexts and -XUndecideableInstances to allow this instance declaration, but that's fair enough.

The same applies to data type declarations involving type functions.

Variations (not implemented)

This section collects some un-implemented ideas.

Interaction with "newtype-deriving"

GHC's "newtype deriving mechanism" (see [1]) 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.)

This situation is expected to be common, as the main use of the standalone feature is to obtain derived instances that were omitted when the data type was defined.

But, that means whether or not an instance was derived is now part of the module's. Programs would be able to use this (mis)feature to perform a compile-time check and execute code differently depending on whether any given instance is derived or hand-coded:

   module MA(A) where
   data A = A deriving Show
  
   module MB(B) where
   data B = B deriving Show

   module MC where
   import MA
   import MB

   -- verify that the A and B Show instances were derived
   -- (they need to be derived to ensure the output can
   -- be parsed in our non-Haskell code).
   derive instance Show A 
   derive instance Show B

The writer of MC already knows that MA and MB defined instances of Show for A and B. He just wants to ensure that nobody changes either module to use a non-derived instance; if someone does try to use a non-derived instance:

   module MA(A) where
   data A = A
   instance Show A where
       show _ = "a"

then they will get an overlapping instance error in MC.

The result is that programs would be able to require, for any Class, not just that an instance of the class was defined for a type, but that a /derived/ instance was defined. Is this good?