I am trying to build a Default class that automagically knows how to create default values. So I read the relevan wiki page and my problem comes down to this: Why does this typecheck:

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DefaultSignatures #-}

import GHC.Generics

-- From https://wiki.haskell.org/GHC.Generics (sort of)
class GSerialize f where
  gput :: f a -> [Int]
class Serialize a where
  put :: a -> [Int]
  default put :: (Generic a, GSerialize (Rep a)) => a -> [Int]
  put a = gput (from a)

But this doesn't

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DefaultSignatures #-}

import GHC.Generics

class GDefault a where
  gdef :: a
class Default a where
  def :: a
  default def :: (Generic a, GDefault (Rep a)) => a
  def = gdef . from

The error is:

• Expecting one more argument to ‘Rep a’
  Expected a type, but ‘Rep a’ has kind ‘* -> *’
• In the first argument of ‘GDefault’, namely ‘Rep a’
  In the type signature:
    def :: (Generic a, GDefault (Rep a)) => a
  In the class declaration for ‘Default’
share
1  
The first class expects its "argument" f to have kind * -> * (since it uses it as f a) but your class argument a (of GDefault) expects only a type (so kind *), but you are still feeding it something of kind * -> *. – Alec Sep 21 '16 at 14:53
    
It's very unclear what this question is asking - the typechecker told you why the latter code doe not compile! Even if your "problem comes down to this" perhaps you should describe the actual problem. – user2407038 Sep 21 '16 at 15:40
    
I feel quite dumb, it's actually what Alec suggests... – fakedrake Sep 21 '16 at 16:20
up vote 2 down vote accepted

The compiler error here is helpful, but only in that annoying way where it tells you exactly what is wrong but not why it is wrong.

Expected a type but "Rep a" has kind "* -> *".

So the problem here is that Rep (a type family) needs two arguments (call them a and p, as in Rep a p); it as a type-level function maps these two type arguments into the "generic" type. For example,

data Empty deriving Generic

instance Generic Empty where
  type Rep Empty =
    D1 ('MetaData "Empty" "Main" "package-name" 'False) V1

-- taken from https://hackage.haskell.org/package/base-4.9.0.0/docs/GHC-Generics.htm
  • a, e.g. Empty, represents the type from which we are genericizing.

  • p is a dummy type so that we can reuse our representation types for higher-level types (see Generic1 in the documentation).

So, in the above example, Rep Empty p would simplify to D1 ('MetaData ...) V1 p.

We can usually ignore p except when it comes to defining new typeclasses that take advantage of generics. We want to pattern match on on types like D1 ('MetaData ...) V1 p but we need some way of handling the extra parameter.

A trick then is to treat D1 ('MetaData ...) V1 like a higher-level type (like a functor). This is our f in GDefault.

class GDefault f where
  gdef :: f a

Yes a will always be this stupid parameter that we will never use, but in return for line noise we get the ability to pattern match on the f in our instances. Here are four instances that allow for automatic generic def implementations for product types (:*: being a lifted tuple):

instance GDefault U1 where
  gdef = U1

instance Default a => GDefault (K1 i a) where
  gdef = K1 def

instance (GDefault a, GDefault b) => GDefault (a :*: b) where
  gdef = gdef :*: gdef

instance GDefault a => GDefault (M1 i c a) where
  gdef = M1 gdef

This, along with some sensible defaults for the numeric tower, will let us define datatypes like data Foo = Foo Int Char Float deriving (Show, Generic) and evaluate show (def :: Foo) to "Foo 0 0 0.0".

Your code had gdef :: a, which is the wrong kind. We want gdef :: f a because the typeclass is defined on types with kind * -> *, hence the error message.

And to take advantage of this helper class, we do much as you did:

class Default a where
  def :: a

  default def :: (Generic a, GDefault (Rep a)) => a
  def = to gdef

to :: Rep a x -> a introduces a spurious x, which unifies with our gdef :: f a to produce f ~ Rep a, throwing away the x and being exactly what we intended.

You can see this approach elaborated in the data-default package.

share

Your Answer

 
discard

By posting your answer, you agree to the privacy policy and terms of service.

Not the answer you're looking for? Browse other questions tagged or ask your own question.