[Haskell-cafe] Mixing own and derived instances with Generic Deriving Mechanism

José Pedro Magalhães jpm at cs.uu.nl
Sun Feb 2 16:02:31 UTC 2014


Hi Maarten,

The problem here is that your instance of GShow MyFancyType defines gshow,
but the
function that is defined generically is actually gshowsPrec, with the
others being given
defaults. For this to work as you'd expect it to, you have to define
gshowsPrec in the
instance GShow MyFancyType. This is a bit unfortunate, but because
gshowsPrec has
a generic default, it cannot have the usual default (like showsPrec does).


Cheers,
Pedro



On Sat, Feb 1, 2014 at 12:11 PM, Maarten Faddegon <
haskell-cafe at maartenfaddegon.nl> wrote:

> Dear Pedro, Cafe,
>
> Thanks again for helping me out last December. I have been
> playing a bit more with deriving show and now ran into an
> interesting problem mixing my own instances with derived
> instances. Hope you can enlighten me there!
>
> > {-# LANGUAGE DeriveGeneric #-}
> > module Test where
> > import GHC.Generics
> > import Generics.Deriving.Show
>
> The Generic Deriving Mechanism adds the keyword 'default' to
> class definitions.  With this keyword we can define a
> type-generic definition of that method when not given. For
> example, if we define our own MyData type, we can derive the
> GShow methods:
>
> > data MyData = MyData MyFancyType deriving Generic
> > instance GShow MyData
>
> We can also still give our own definition, for example if we want
> values of the MyFancyType to always be shown as the same string:
>
> > data MyFancyType = MyFancy1 | MyFancy2 deriving Generic
> > instance GShow MyFancyType where
> >       gshow _ = "Fancy!"
>
> There is something strange here though: when we use gshow
> directly on a MyFancyType value our own instance definition is
> used, evaluating as expected to "Fancy!".
>
> > ex1 = gshow MyFancy1
>
> But as soon as we are inside a derived method, we will continue
> using derived instances even though we defined our own. The
> example below evaluates to "MyData MyFancy1", rather than "MyData
> Fancy!":
>
> > ex2 = gshow (MyData MyFancy1)
>
> The default methods of GShow are defined in terms of methods from
> GShow' which operate on the type-representation. From this
> representation I do not see a way to recover the information
> that a type has a GShow instance.  Am I correct (I hope not :) or
> is there a way out?
>
> Cheers,
>
> Maarten Faddegon
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140202/2a24173b/attachment.html>


More information about the Haskell-Cafe mailing list