[GHC] #13758: Deriving can't find an instance that holds, standalone deriving works

GHC ghc-devs at haskell.org
Fri May 26 20:19:55 UTC 2017


#13758: Deriving can't find an instance that holds, standalone deriving works
-------------------------------------+-------------------------------------
           Reporter:  Iceland_jack   |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Using [https://hackage.haskell.org/package/generic-deriving-1.11.2/docs
 /Generics-Deriving-Monoid.html generic-deriving] works

 {{{#!hs
 {-# Language ScopedTypeVariables, GeneralizedNewtypeDeriving,
 DeriveGeneric, UndecidableInstances, StandaloneDeriving, FlexibleContexts
 #-}

 import GHC.Generics
 import Generics.Deriving.Monoid hiding (GMonoid)
 import Data.Coerce
 import Data.Constraint

 import Data.Semigroup
 newtype GenericMonoid a = GenericMonoid a

 instance (Generic a, Monoid' (Rep a)) => Semigroup (GenericMonoid a) where
   (<>) = coerce (mappenddefault :: a -> a -> a)

 instance (Generic a, Monoid' (Rep a)) => Monoid (GenericMonoid a) where
   mempty  = coerce (memptydefault  :: a)
   mappend = coerce (mappenddefault :: a -> a -> a)

 data Urls = Urls String String String
   deriving (Show, Generic)

 newtype UrlsDeriv = UD (GenericMonoid Urls)

 deriving instance Semigroup UrlsDeriv
 deriving instance Monoid    UrlsDeriv
 }}}

 but changing that to

 {{{#!hs
 newtype UrlsDeriv = UD (GenericMonoid Urls)
   deriving (Semigroup, Monoid)
 }}}

 fails

 {{{
 $ ghci -ignore-dot-ghci tWqD.hs
 GHCi, version 8.0.1: http://www.haskell.org/ghc/  :? for help
 [1 of 1] Compiling Main             ( tWqD.hs, interpreted )
 Ok, modules loaded: Main.
 *Main> :r
 [1 of 1] Compiling Main             ( tWqD.hs, interpreted )

 tWqD.hs:26:13: error:
     • No instance for (Monoid' (Rep Urls))
         arising from the 'deriving' clause of a data type declaration
       Possible fix:
         use a standalone 'deriving instance' declaration,
           so you can specify the instance context yourself
     • When deriving the instance for (Semigroup UrlsDeriv)

 tWqD.hs:26:24: error:
     • No instance for (Monoid' (Rep Urls))
         arising from the 'deriving' clause of a data type declaration
       Possible fix:
         use a standalone 'deriving instance' declaration,
           so you can specify the instance context yourself
     • When deriving the instance for (Monoid UrlsDeriv)
 Failed, modules loaded: none.
 }}}

 This feels familiar but I couldn't quickly. I can't recall if this
 behavior is intended so I'm filing a ticket just in case.

 It even following proof of `Monoid' (Rep Urls)` and a dummy quasiquote
 `pure []` separating it them,

 {{{#!hs
 {-# Language ..., TemplateHaskell #-}

 ...

 doo :: Dict (Monoid' (Rep Urls))
 doo = Dict

 pure []

 newtype UrlsDeriv = UD (GenericMonoid Urls)
   deriving Monoid
 }}}

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


More information about the ghc-tickets mailing list