I have a typeclass Cyclic
for which I would like to be able to provide generic instances.
class Cyclic g where
gen :: g
rot :: g -> g
ord :: g -> Int
Given a sum type of nullary constructors,
data T3 = A | B | C deriving (Generic, Show)
I want to generate an instance equivalent to this:
instance Cyclic T3 where
gen = A
rot A = B
rot B = C
rot C = A
ord _ = 3
I've tried to work out the required Generic
machinery like so
{-# LANGUAGE DefaultSignatures, FlexibleContexts, ScopedTypeVariables, TypeOperators #-}
import GHC.Generics
class GCyclic f where
ggen :: f a
grot :: f a -> f a
gord :: f a -> Int
instance GCyclic U1 where
ggen = U1
grot _ = U1
gord _ = 1
instance Cyclic c => GCyclic (K1 i c) where
ggen = K1 gen
grot (K1 a) = K1 (rot a)
gord (K1 a) = ord a
instance GCyclic f => GCyclic (M1 i c f) where
ggen = M1 ggen
grot (M1 a) = M1 (grot a)
gord (M1 a) = gord a
instance (GCyclic f, GCyclic g) => GCyclic (f :*: g) where
ggen = ggen :*: ggen
grot (a :*: b) = grot a :*: grot b
gord (a :*: b) = gord a `lcm` gord b
instance (GCyclic f, GCyclic g) => GCyclic (f :+: g) where
ggen = L1 ggen
-- grot is incorrect
grot (L1 a) = L1 (grot a)
grot (R1 b) = R1 (grot b)
gord _ = gord (undefined :: f a)
+ gord (undefined :: g b)
Now I can provide default implementations for Cyclic
using GCyclic
:
class Cyclic g where
gen :: g
rot :: g -> g
ord :: g -> Int
default gen :: (Generic g, GCyclic (Rep g)) => g
gen = to ggen
default rot :: (Generic g, GCyclic (Rep g)) => g -> g
rot = to . grot . from
default ord :: (Generic g, GCyclic (Rep g)) => g -> Int
ord = gord . from
but my GCyclic
instances are incorrect. Using T3
from above
λ. map rot [A, B, C] -- == [B, C, A]
[A, B, C]
It's clear why rot
is equivalent to id
here. grot
recurses down the (:+:)
structure of T3
until it hits the base case grot U1 = U1
.
It was suggested on #haskell
to make use of constructor information from M1
so grot
can choose the next constructor to recurse on, but I'm not sure how to do this.
Is it possible to generate the desired instances of Cyclic
using GHC.Generics
or some other form of Scrap Your Boilerplate?
EDIT: I could write Cyclic
using Bounded
and Enum
class Cyclic g where
gen :: g
rot :: g -> g
ord :: g -> Int
default gen :: Bounded g => g
gen = minBound
default rot :: (Bounded g, Enum g, Eq g) => g -> g
rot g | g == maxBound = minBound
| otherwise = succ g
default ord :: (Bounded g, Enum g) => g -> Int
ord g = 1 + fromEnum (maxBound `asTypeOf` g)
but (as is) this is unsatisfying, as it requires all of Bounded
, Enum
and Eq
. Additionally, Enum
cannot be automatically derived by GHC in some cases whereas the more robust Generic
can.
Bounded
andEq
is the ability to tell when you're at the last item to start iterating from some othergen
again, which is what my answer adds. Note that addingglast
toGCylic
doesn't require that you add a corresponding function toCyclic
unless you intend to derive instances forK1
(which you should totally do because it's awesome; the derived instance for[T3]
might surprise you; it surprised me). – Seemaundefined
values as proxies for types, everything that implementsCyclic
needs to acceptundefined
values, since some implementation might passundefined
to the other ones. You can avoid this by instead usingdata Proxy a = Proxy
from the tagged package (hackage.haskell.org/package/tagged) and pass around(Proxy :: ...)
instead. You'd change toord :: Proxy a -> Int
. – Seemaglast
abstaction to leak intoCyclic
. I stubbedgend
forK1
withconst False
, and derivedinstance Cyclic [T3]
. The result is pretty interesting,iterate rot (gen :: [T3]) -> [[], [A], [B,A], [C,B,A], [A,C,B,A] ...]
. Is that what you meant? – Sculpsitgen
. Imagine the functionrotIsGen :: (Eq a, Cyclic a) => a -> Bool
whererotIsGen = (==gen) . rot
. – Seemaforall a. Cyclic a => a
because I want to write functions polymorphic ina
. If I don't exportCyclic
(so no new instances can be written) and I choose the instances ofCyclic
carefully I can be sure that the are no instances ofEq
, so functions likerotIsGen
can be avoided.gen
also happens to fit into the abstraction as the generator of a cyclic group. – SculpsitrotIsGen
forK1
is wrong; it makesgen
too special. Consideriterate rot $ (Left (True, False) :: Either (Bool, Bool) T3)
. It only ever visitsLeft (True, False)
andLeft (False, True)
, which has only 2 elements. On the other handLeft (False, False)
generates[Left (False, False), Left (True, True), Right A, Right B, Right C, Left (False, False), ...
– SeemaK1
, how would you implementglast
forK1
? – Sculpsitglast
forK1
isn't the problem, it'srotIsEnd
for theCycle
, the problem is in theGCycle
instance for products (:*:
), since the product of two cyclic groups is a cyclic group iff their orders are coprime. math.stackexchange.com/questions/5969/… – SeemaT3
, there are a few other approaches you could take. You could moveord
to the type level and require a type-level proof of the co-primeness ofCyclic
s before deriving a product for them. You could only derive product instances for a type that provides a type-level proof that the values were arrived at by rotating the generator. You could change the interface of cyclic so that arbitrary values of the type can't be rotated. – Seema