Reputation: 3633
I'm trying to write a generic vector space implementation in Haskell. My implementation is as follows:
import qualified GHC.Generics as G
import GHC.Generics hiding (V1)
class GVecSpace v where
addVs :: v -> v -> v
scaleV :: Double -> v -> v
instance GVecSpace (G.V1 a) where
addVs _ _ = undefined
scaleV _ _ = undefined
instance GVecSpace (G.U1 a) where
addVs _ x = x -- no value
scaleV _ x = x -- no value
instance (GVecSpace (f a), GVecSpace (g a)) => GVecSpace ((f :+: g) a) where
addVs (L1 x) (L1 y) = L1 $ addVs x y
addVs (R1 x) (R1 y) = R1 $ addVs x y
scaleV d (L1 x) = L1 $ scaleV d x
scaleV d (R1 x) = R1 $ scaleV d x
instance (GVecSpace (f a), GVecSpace (g a)) => GVecSpace ((f :*: g) a) where
addVs (x1 :*: x2) (y1 :*: y2) =
addVs x1 y1 :*: addVs x2 y2
scaleV d (x1 :*: x2) =
scaleV d x1 :*: scaleV d x2
instance (GVecSpace c) => GVecSpace (K1 i c p) where
addVs (K1 x) (K1 y) = K1 $ addVs x y
scaleV d (K1 x) = K1 $ scaleV d x
instance (GVecSpace (f p)) => GVecSpace (M1 i c f p) where
addVs (M1 x) (M1 y) = M1 $ addVs x y
scaleV d (M1 x) = M1 $ scaleV d x
instance (Generic a, GVecSpace (Rep a)) => GVecSpace a where
addVs x y =
G.to $ addVs (G.from x) (G.from y)
scaleV d x =
G.to $ scaleV d (G.from x)
But GHC complains because Rep a
has the wrong kind:
Expecting one more argument to ‘Rep a’
The first argument of ‘GVecSpace’ should have kind ‘*’,
but ‘Rep a’ has kind ‘* -> *’
In the instance declaration for ‘GVecSpace a’
What should I change to make this work? One option is to make GVecSpace
only work for kinds of * -> *
, but that seems awkward. Is there a way to avoid that?
Upvotes: 2
Views: 106
Reputation: 24156
To make a library that uses GHC.Generics
we first need a few pre-requisites.
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
import GHC.Generics as G
All of the representations for generics carry around an extra type parameter called "the parameter" p
. You can see this in the kind of the type Rep a
in the Generic a
class, type Rep a :: * -> *
. The representation for a data type isn't just another data type, it's a type with the kind * -> *
, the same kind as Functor
s and Monad
s. It take another type as a parameter. Most of the time defining instances for a class based on the generic representations, we will just ignore the parameter.
Due to the extra parameter, it's useful to define a non-generic class. We'll be adding more to this later.
class VecSpace v where
addVs :: v -> v -> v
scaleV :: Double -> v -> v
...
The generic version of the class, GVecSpace
, has an extra parameter a
on the types of all the values. Everywhere we used v
before, we will use f a
. We will make new names for GVecSpace
by prepending g
to the names from VecSpace
.
class GVecSpace f where
gaddVs :: f a -> f a -> f a
gscaleV :: Double -> f a -> f a
The GVecSpace
class is a little awkward and only works for the kind * -> *
, but it is only used for making the default implementations for VecSpace
. You will use VecSpace
everywhere else.
Unit types with only a single constructor are vector spaces. Note that G.U1
is not applied to a parameter.
instance GVecSpace G.U1 where
gaddVs _ x = x -- no value
gscaleV _ x = x -- no value
The product of two vector spaces is a vector space. Note that f
and g
and f :*: g
aren't applied to a parameter type.
instance (GVecSpace f, GVecSpace g) => GVecSpace (f :*: g) where
gaddVs (x1 :*: x2) (y1 :*: y2) =
gaddVs x1 y1 :*: gaddVs x2 y2
gscaleV d (x1 :*: x2) =
gscaleV d x1 :*: gscaleV d x2
For K1
we drop the final parameter p
from the type, and define it in terms of the non-generic VecSpace
. The c
parameter only has kind *
, an ordinary type, so it can't be an instance of GVecSpace
.
instance (VecSpace c) => GVecSpace (K1 i c) where
gaddVs (K1 x) (K1 y) = K1 $ addVs x y
gscaleV d (K1 x) = K1 $ scaleV d x
For M1
metadata nodes, we drop the final paramter p
from the type.
instance (GVecSpace f) => GVecSpace (M1 i c f) where
gaddVs (M1 x) (M1 y) = M1 $ gaddVs x y
gscaleV d (M1 x) = M1 $ gscaleV d x
Now we can return to the VecSpace
class and fill in the defaults for how something is a VecSpace
when its representation has a GVecSpace
instance. We convert the arguments into the representation from
the type v
, perform the generic version of the operation on the representation, and then convert back to
the type v
when we're done.
class VecSpace v where
addVs :: v -> v -> v
scaleV :: Double -> v -> v
default addVs :: (Generic v, GVecSpace (Rep v)) => v -> v -> v
addVs x y = to (gaddVs (from x) (from y))
default scaleV :: (Generic v, GVecSpace (Rep v)) => Double -> v -> v
scaleV s = to . gscaleV s . from
Assuming you have already observed that Double
s form a vector space
instance VecSpace Double where
addVs = (+)
scaleV = (*)
we can derive a working VecSpace
instance for tuples in terms of the default
s in VecSpace
.
instance (VecSpace a, VecSpace b) => VecSpace (a, b)
Upvotes: 4