[GHC] #10607: Auto derive from top to bottom

GHC ghc-devs at haskell.org
Wed Oct 21 11:22:23 UTC 2015


#10607: Auto derive from top to bottom
-------------------------------------+-------------------------------------
        Reporter:  songzh            |                Owner:
            Type:  feature request   |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  7.11
      Resolution:                    |             Keywords:  deriving,
                                     |  typeclass, auto
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by songzh):

 Replying to [comment:7 goldfire]:
 > Replying to [comment:6 songzh]:
 > >
 > > 1. It forces me to use `KindSignatures`, `ConstraintKind` and other
 extension which should not be needed.(please see `TopDownDeriveTest.hs`
 file)
 >
 > Fair enough. But, in truth, you ''might'' need these extensions,
 depending on the definitions of types you are deriving for. One way
 forward here is to allow Template Haskell to turn on some extensions just
 within a splice, instead of specifying them at the top of a file. (This
 actually shouldn't be hard, once #10820 is complete.)
 >



 1. Thanks very much. I will watch the ticket.

 > >
 > > 2. For type synonym, I want to do it without using
 TypeSynonymInstance, but I am not sure how to get the arity of a type
 constructor. For example: `type T a = (a,a,a,a,a)` I need to generate (Eq
 a , Eq b, Eq c ,Eq d, Eq e) => (a,b,c,d,e). However, the type synonym can
 be eta reduced, what should do to handle this case?
 >
 > I'm not sure what the problem is here. Are you worried about deriving,
 say, `Functor`, for which the eta reduction is necessary? But your example
 actually cannot be eta-reduced, because the variable `a` is used multiple
 times in the RHS. So I'm not sure what you're getting at on this one.
 >
 > >


 2. I will try to solve it, just not sure about how to handle `TySynD`
 case.
 {{{
 getTyVarCons :: Name -> Q ([TyVarBndr], [Con])
 getTyVarCons name = do
         info <- reify name
         case info of
              TyConI dec ->
                 case dec of
                      DataD    _ _ tvbs cons _ -> return (tvbs,cons)
                      NewtypeD _ _ tvbs con  _ -> return (tvbs,[con])
                      TySynD   _ vars type'    -> undefined -- need to
 handle type eta reduction
                      _ -> error "must be data, newtype definition or type
 synonym!"
              _ -> error "bad type name, quoted name is not a type!"
 }}}
 You can see that I am not sure how to handle `TySynD` case. If the user
 declares
 {{{
 data A a b c = A a b c
 type A' a = A a String a
 }}}





 > > 3. When I derive some instances that based on Generic class like
 Binary or FromJSON it gives me a type error:
 > >
 > > {{{
 > >     Could not deduce (G.Generic a)
 > >       arising from a use of `binary-0.7.6.1:Data.Binary.Class.$gdmget'
 > >     from the context (B.Binary a)
 > >       bound by the instance declaration
 > > }}}
 > >
 > > while I think `deriving instance (Binary a ,Binary b) => Binary (A a
 b)` should work fine. Why do I have to write `deriving instance (B.Binary
 a, G.Generic a) => (B.Binary (B a))`? And could you give me some
 suggestions to solve it.
 >
 > I'm a little lost here. What's the code being type-checked? What's `A`?
 What's `B`? Does the error happen both with and without TH? Or only when
 using TH?

 3. Sorry for confusing you. Normmally, I derive the type classes in the
 following way:
 {{{
 {-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE DeriveAnyClass #-}

 import qualified GHC.Generics as G
 import qualified Data.Binary as B

 data C a b = A (B a) deriving (Eq, G.Generic, Ord)
 data B a = B a | F (D a) deriving (Eq, G.Generic, Ord)
 data D b = D b | E b deriving (Eq, G.Generic, Ord)

 deriving instance B.Binary b => B.Binary (D b)
 deriving instance B.Binary a => B.Binary (B a)
 deriving instance (B.Binary a , B.Binary b) => (B.Binary (C a b))
 }}}
 For standalone deriving `(B.Binary (C a b))`, I do not need to give
 `G.Generic a` and `G.Generic b` in its context. However, if I derive
 `G.Generic` for `C` by using standalone deriving, GHC complains that I did
 not give `G.Generic` in context `(B.Binary a, B.Binary b)`

 {{{
 {-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE DeriveAnyClass #-}

 import qualified GHC.Generics as G
 import qualified Data.Binary as B

 data C a b = A (B a) deriving (Eq, Ord)
 data B a = B a | F (D a) deriving (Eq, G.Generic, Ord)
 data D b = D b | E b deriving (Eq, G.Generic, Ord)

 deriving instance (G.Generic a, G.Generic b) => (G.Generic (C a b))

 deriving instance B.Binary b => B.Binary (D b)
 deriving instance B.Binary a => B.Binary (B a)
 deriving instance (B.Binary a , B.Binary b) => (B.Binary (C a b))
 }}}

 This means that I have to discriminate generic standalone deriving(i.e.
 with `G.Generic` context) and non-generic standalone deriving(i.e. without
 `G.Generic` context), which is not very nice. Are there any way to solve
 this.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10607#comment:9>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list