I would like to derive with the anyclass
strategy for the class Zeros
. For this i need a default implementation and the corresponding instances for
Ok, since you said in the comments that what you're aiming for semantically is something like deriving Monoid
, let's do that.
A class like Monoid
is easy to derive for "sum types", i.e., types having more than one constructor, but it is possible to derive it for pure "product types", i.e., types having a single constructor and just one or more arguments. Let's focus just on zero
, which corresponds to mempty
, and is the subject of your question:
if the single constructor has no arguments, we simply use that constructor,
if the single constructor has one argument (as your B1
example), then we require that argument to have a Zero
instance already and use the zero
of that type,
if the single constructor has more than one argument, we do the same for all these arguments: we require all of them to have a Zero
instance and then use zero
for all of these.
So really, we can phrase this as one simple rule: for all arguments of the single constructor, just apply zero
.
We have the choice of several approaches to generic programming to implement this rule. You've been asking about GHC.Generics
, and I will explain how to do it in that approach, but let me nevertheless first explain how to do it with the generics-sop package, because I think one can more directly transcribe the rule identified above into code in this approach.
With generics-sop, your code looks as follows:
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE StandaloneDeriving #-}
module Zero where
import qualified GHC.Generics as GHC
import Generics.SOP
class Zero a where
zero :: a
default zero :: (IsProductType a xs, All Zero xs) => a
zero = to (SOP (Z (hcpure (Proxy @Zero) (I zero))))
instance Zero Int where
zero = 0
Most of the code is enabling language extensions and the module header. Let's look at the rest:
We are declaring the Zero
class with the zero
method as you did. Then we give a default signature for the zero
method explaining under which conditions we can derive it. The type signature says that the type has to be a product type (i.e., have a single constructor). The xs
is then bound to a list of types corresponding to the types of all the constructor arguments. The All Zero xs
constraint says that all these argument types also have to be an instance of the Zero
class.
The code is then a one-liner, although admittedly a lot is going on in that line. The to
call in transforms the produces generic representation into a value of the actually desired type in the end. The SOP . Z
combination says we want to produce a value of the first (and only) constructor of the datatype. The hcpure (Proxy @Zero) (I zero)
call produces as many copies of calls to zero
as there are arguments of the constructor.
In order to try it, we can define datatypes and derive instances of Zero
for them now:
data B1 = B1 Int
deriving (GHC.Generic, Generic, Show)
deriving instance Zero B1
data B2 = B2 Int B1 Int
deriving (GHC.Generic, Generic, Show)
deriving instance Zero B2
Because generics-sop is built on top of GHC generics, we have to define two Generic
classes. The GHC.Generic
class built into GHC, and the Generic
class provided by generics-sop. The Show
class is just for convience and testing.
It's a bit unfortunate that even with the DeriveAnyClass
extension, we cannot simply add Zero
to the list of derived instances here, because GHC has difficulties inferring that the instance context should actually be empty. Perhaps a future version of GHC will be clever enough to recognise this. But in a standalone deriving declaration, we can explicitly provide the (empty) instance context and it is fine. In GHCi, we can see that this works:
GHCi> zero :: B1
B1 0
GHCi> zero :: B2
B2 0 (B1 0) 0
Let's look how we can do the same thing directly with GHC generics. Here, the code looks as follows:
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeOperators #-}
module Zero where
import GHC.Generics
class Zero a where
zero :: a
default zero :: (Generic a, GZero (Rep a)) => a
zero = to gzero
instance Zero Int where
zero = 0
class GZero a where
gzero :: a x
instance GZero U1 where
gzero = U1
instance Zero a => GZero (K1 i a) where
gzero = K1 zero
instance (GZero a, GZero b) => GZero (a :*: b) where
gzero = gzero :*: gzero
instance GZero a => GZero (M1 i c a) where
gzero = M1 gzero
The start is mostly what you also had in your question. The default signature for zero
says that if a
has a Generic
instance and the type's generic representation Rep a
is an instance of GZero
, we can obtain a definition of zero
by first calling gzero
, and then using to
to transform the generic representation into the actual type.
We now have to give instances for the GZero
class. We provide instances for U1
, K1
, (:*:)
and M1
, telling GHC how to deal with unit types (i.e., constructors without arguments), constants, pairs (binary products) and metadata, respectively. By not providing an instance for (:+:)
, we implicitly exclude sum types (which was a bit more explicit via the IsProductType
constraint in generics-sop).
The instance for U1
says that for a unit type we simply return the unique value.
The instance for constants (these are the arguments of a constructor) says that for these, we need them to also be an instance of the Zero
class and use a recursive call to zero
.
The instance for pairs says that in this case we produce a pair of gzero
calls. This instance is applied repeatedly if a constructor has more than two arguments.
The instance for metadata says that we want to ignore all metadata such as constructor names and record field selectors. We did not have to do anything about metadata in generics-sop, because GHC generics mixes metadata into the representation of every value, whereas in generics-sop it is separate.
From here one, it's basically the same:
data B1 = B1 Int
deriving (Generic, Show, Zero)
data B2 = B2 Int B1 Int
deriving (Generic, Show, Zero)
This is a bit simpler, as we only have to derive a single Generic
class, and in this scenario, GHC is clever enough to figure out the instance context for Zero
, so we can just add it to the list of derived instances. The interaction with GHCi is exactly the same, so I won't repeat it here.
Now that we have zero
which corresponds to mzero
, perhaps you want to extend the class to cover mappend
next. This is also possible, and of course, you're welcome to try it as an exercise.
If you want to see solutions:
For generics-sop, you can look at my ZuriHac talk from 2016 which explains generics-sop in a bit more detail and uses how to derive Monoid
instances as the initial example.
For GHC generics, you can look at the generic-deriving package which contains many example generic programs, including monoids. The source code
of the Generics.Deriving.Monoid module contains the class instances for GMonoid'
which are corresponding to GZero
above and also contain code for mappend
.