GHC/Stand-alone deriving declarations: Difference between revisions

From HaskellWiki
< GHC
(Links updated.)
(fix link to ghc user guide)
 
(7 intermediate revisions by 6 users not shown)
Line 1: Line 1:
[[Category:GHC|Stand-alone deriving declarations]]
[[Category:GHC|Stand-alone deriving declarations]]
{{GHCUsersGuide|exts/standalone_deriving|| a StandaloneDeriving section}}


''This page is from an early point in the life of the stand-alone deriving mechanism. Please see the linked documentation for an up-to-date account of the present situation.''
''This page is from an early point in the life of the stand-alone deriving mechanism. Please see the linked documentation for an up-to-date account of the present situation.''
Line 5: Line 7:
== Standalone deriving ==
== Standalone deriving ==


GHC supports so-called "stand-alone deriving" declarations, which are described in the [http://www.haskell.org/ghc/dist/current/docs/users_guide/deriving.html#stand-alone-deriving user manual section].
This page mentions points that may not be immediately obvious from the manual.


This page mentions points that may not be immediately obvious from the manual.
 
== Deriving data types with non-standard contexts ==
== Deriving data types with non-standard contexts ==


Line 22: Line 22:
all that tiresome code for equality.  Standalone deriving lets you supply the context yourself, but have GHC write the code:
all that tiresome code for equality.  Standalone deriving lets you supply the context yourself, but have GHC write the code:
<haskell>
<haskell>
  data T m = MkT (m Int)
data T m = MkT (m Int)
 
deriving instance Eq (m Int) => Eq (T m)
  deriving instance Eq (m Int) => Eq (T m)
</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.
Of course, you'll need to add the flags <hask>-XFlexibleContexts</hask> and <hask>-XUndecidableInstances</hask> to allow this instance declaration, but that's fair enough.


The same applies to data type declarations involving type functions.
The same applies to data type declarations involving type functions.
Line 40: Line 39:
   deriving instance C a Foo
   deriving instance C a 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 parameterYou 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 an 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
  newtype Bar = B Bool
newtype Bar = B Bool
  deriving instance C Foo Bar
deriving 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
  instance C Int Bar  => C Foo Bar
instance C Int Bar  => C Foo Bar
  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.
Line 56: Line 55:
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  
  instance SetLike IntSet Int where
instance SetLike IntSet Int where
 
  newtype Id = Id Int
  newtype IdSet = IdSet IntSet
   
   
  deriving instance SetLike IntSet Int => SetLike IdSet Id
newtype Id = Id Int
newtype IdSet = IdSet IntSet
deriving instance SetLike IntSet Int => SetLike IdSet Id
</haskell>
</haskell>


Line 77: Line 75:
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:
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:
<haskell>
<haskell>
  module MA(A) where
module MA(A) where
  data A = A deriving Show
data A = A deriving Show
 
 
  module MB(B) where
module MB(B) where
  data B = B deriving Show
data B = B deriving Show


  module MC where
module MC where
  import MA
import MA
  import MB
import MB


  -- verify that the A and B Show instances were derived
-- verify that the A and B Show instances were derived
  -- (they need to be derived to ensure the output can
-- (they need to be derived to ensure the output can
  -- be parsed in our non-Haskell code).
-- be parsed in our non-Haskell code).
  deriving instance Show A  
deriving instance Show A  
  deriving instance Show B
deriving instance Show B
</haskell>
</haskell>
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:
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:
<haskell>
<haskell>
  module MA(A) where
module MA(A) where
  data A = A
data A = A
  instance Show A where
instance Show A where
      show _ = "a"
    show _ = "a"
</haskell>
</haskell>
then they will get an overlapping instance error in MC.  
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?
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?

Latest revision as of 22:49, 12 June 2021


The GHC Users Guide has a StandaloneDeriving section.

This page is from an early point in the life of the stand-alone deriving mechanism. Please see the linked documentation for an up-to-date account of the present situation.

Standalone deriving

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 -XUndecidableInstances 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 instance C a Foo

(where Foo is the newtype), and get an instance for (C a Foo). But what if you want an 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
deriving 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
deriving instance SetLike IntSet Int => SetLike IdSet Id

Duplicate instances

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

  deriving 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).
deriving instance Show A 
deriving 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?