Search code examples
haskellgeneric-programming

Datatype-generic programming and the mysterious gdmXXX


I'm using datatype-generic programming for a class called Generic that contains a method called get. If my end user defines a type and forgets to add deriving Generic, and calls put, they will see an error message such as this:

No instance for (ALife.Creatur.Genetics.Code.BRGCWord8.GGene
(GHC.Generics.Rep ClassifierGene))
arising from a use of `ALife.Creatur.Genetics.Code.BRGCWord8.$gdmput'

I can tell users how to fix the error, but I am curious about this $gdmput. I assume it's a function or symbol that's automatically generated, but by what? Is it the use of the DefaultSignatures pragma, or the DeriveGeneric pragma? I read a few papers about datatype-generic programming, but did not see any reference to gdmXXX symbols.

Here's the definition of the Generic class.

{-# LANGUAGE TypeFamilies, FlexibleContexts, FlexibleInstances,
    DefaultSignatures, DeriveGeneric, TypeOperators #-}
. . .

-- | A class representing anything which is represented in, and
--   determined by, an agent's genome.
--   This might include traits, parameters, "organs" (components of
--   agents), or even entire agents.
--   Instances of this class can be thought of as genes, i.e.,
--   instructions for building an agent.
class Genetic g where
  -- | Writes a gene to a sequence.
  put :: g -> Writer ()

  default put :: (Generic g, GGenetic (Rep g)) => g -> Writer ()
  put = gput . from

  -- | Reads the next gene in a sequence.
  get :: Reader (Either [String] g)

  default get :: (Generic g, GGenetic (Rep g)) => Reader (Either [String] g)
  get = do
    a <- gget
    return $ fmap to a

  getWithDefault :: g -> Reader g
  getWithDefault d = fmap (fromEither d) get

class GGenetic f where
  gput :: f a -> Writer ()
  gget :: Reader (Either [String] (f a))

-- | Unit: used for constructors without arguments
instance GGenetic U1 where
  gput U1 = return ()
  gget = return (Right U1)

-- | Constants, additional parameters and recursion of kind *
instance (GGenetic a, GGenetic b) => GGenetic (a :*: b) where
  gput (a :*: b) = gput a >> gput b
  gget = do
    a <- gget
    b <- gget
    return $ (:*:) <$> a <*> b

-- | Meta-information (constructor names, etc.)
instance (GGenetic a, GGenetic b) => GGenetic (a :+: b) where
  gput (L1 x) = putRawWord16 0 >> gput x
  gput (R1 x) = putRawWord16 1 >> gput x
  gget = do
    a <- getRawWord16
    case a of
      Right x -> do
        if even x -- Only care about the last bit
          then fmap (fmap L1) gget
          else fmap (fmap R1) gget
      Left s -> return $ Left s

-- | Sums: encode choice between constructors
instance (GGenetic a) => GGenetic (M1 i c a) where
  gput (M1 x) = gput x
  gget = fmap (fmap M1) gget

-- | Products: encode multiple arguments to constructors
instance (Genetic a) => GGenetic (K1 i a) where
  gput (K1 x) = put x
  gget = do
    a <- get
    return $ fmap K1 a

Solution

  • The $gdm comes from DefaultSignatures. Here's a minimal example that produces a similar error message

    {-# LANGUAGE DefaultSignatures #-}
    
    data NoInstances = NoInstances
    
    class Display a where
        display :: a -> String
    
        default display :: Show a => a -> String
        display = show
    
    instance Display NoInstances
    

    The error message produced is

    defaultsignatures.hs:11:10:
        No instance for (Show NoInstances)
          arising from a use of `Main.$gdmdisplay'
        In the expression: Main.$gdmdisplay
        In an equation for `display': display = Main.$gdmdisplay
        In the instance declaration for `Display NoInstances'