Deriving default instances using GHC.Generics
Asked Answered
S

1

9

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.

Sculpsit answered 3/4, 2014 at 23:39 Comment(11)
Maybe this doesn't fit your problem exactly, but you can provide sane defaults for those functions using just Enum and Bounded. Then all you have to do is declare the instance, no specific implementation needed. I'm on my phone right now, but I can provide an example later. I get the feeling that your actual use case is a bit more complicated though.Timetable
The only thing you need from Bounded and Eq is the ability to tell when you're at the last item to start iterating from some other gen again, which is what my answer adds. Note that adding glast to GCylic doesn't require that you add a corresponding function to Cyclic unless you intend to derive instances for K1 (which you should totally do because it's awesome; the derived instance for [T3] might surprise you; it surprised me).Seema
If you're going to start passing around undefined values as proxies for types, everything that implements Cyclic needs to accept undefined values, since some implementation might pass undefined to the other ones. You can avoid this by instead using data Proxy a = Proxy from the tagged package (hackage.haskell.org/package/tagged) and pass around (Proxy :: ...) instead. You'd change to ord :: Proxy a -> Int.Seema
I don't want the glast abstaction to leak into Cyclic. I stubbed gend for K1 with const False, and derived instance 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?Sculpsit
Yeah, that's what surprised me for a moment.Seema
You're already leaking a special point in the cycle due to gen. Imagine the function rotIsGen :: (Eq a, Cyclic a) => a -> Bool where rotIsGen = (==gen) . rot.Seema
That's a good point, but I need a way to produce a value of type forall a. Cyclic a => a because I want to write functions polymorphic in a. If I don't export Cyclic (so no new instances can be written) and I choose the instances of Cyclic carefully I can be sure that the are no instances of Eq, so functions like rotIsGen can be avoided. gen also happens to fit into the abstraction as the generator of a cyclic group.Sculpsit
Recursing through rotIsGen for K1 is wrong; it makes gen too special. Consider iterate rot $ (Left (True, False) :: Either (Bool, Bool) T3). It only ever visits Left (True, False) and Left (False, True), which has only 2 elements. On the other hand Left (False, False) generates [Left (False, False), Left (True, True), Right A, Right B, Right C, Left (False, False), ...Seema
I'm afraid I don't understand. I've added an instance for K1, how would you implement glast for K1?Sculpsit
glast for K1 isn't the problem, it's rotIsEnd for the Cycle, the problem is in the GCycle instance for products (:*:), since the product of two cyclic groups is a cyclic group iff their orders are coprime. math.stackexchange.com/questions/5969/…Seema
In addition to my more than complete answer, which has gone way beyond deriving an instance for T3, there are a few other approaches you could take. You could move ord to the type level and require a type-level proof of the co-primeness of Cyclics 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
S
5

Edited after rereading what ord is supposed to mean, and again to try to address the product of two cycles problem

You can figure out when to go to the other side of a sum of constructors if you can tell that whats inside is already at the last constructor, which is what the new end and gend functions do. I can't imagine a cyclic group for which we can't define end.

You can implement gord for sums without even examining the values; the ScopedTypeVariables extension helps with this. I've changed the signatues to use proxies, since you're now mixing undefined and trying to deconstruct a value in your code.

import Data.Proxy

Here's the Cyclic class with end, defaults, and Integral n (instead of assuming Int) for ord

class Cyclic g where
    gen :: g
    rot :: g -> g
    end :: g -> Bool
    ord :: Integral n => Proxy g -> n

    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 end :: (Generic g, GCyclic (Rep g)) => g -> Bool
    end = gend . from

    default ord :: (Generic g, GCyclic (Rep g), Integral n) => Proxy g -> n
    ord = gord . fmap from

And the GCyclic class and its implementations:

class GCyclic f where
    ggen :: f a
    gend :: f a -> Bool
    grot :: f a -> f a
    gord :: Integral n => Proxy (f ()) -> n

instance GCyclic U1 where
    ggen   = U1
    grot _ = U1
    gend _ = True
    gord _ = 1

instance Cyclic c => GCyclic (K1 i c) where
    ggen        = K1 gen
    grot (K1 a) = K1 (rot a)
    gend (K1 a) = end a
    gord  _     = ord (Proxy :: Proxy c)

instance GCyclic f => GCyclic (M1 i c f) where
    ggen        = M1    ggen
    grot (M1 a) = M1   (grot a)
    gend (M1 a) = gend  a
    gord  _     = gord (Proxy :: Proxy (f ()))

I can't stress enough that the following is making an equivalence class over multiple cyclic subgroups of the product of the two cycles. Due to the need to detect ends for sums, and the face that the computations for lcm and gcm aren't lazy, we can no longer do fun stuff like derive a cyclic instance for [a].

-- The product of two cyclic groups is a cyclic group iff their orders are coprime, so this shouldn't really work
instance (GCyclic f, GCyclic g) => GCyclic (f :*: g) where
    ggen           = ggen                          :*:  ggen
    grot (a :*: b) = grot  a                       :*:  grot  b
    gend (a :*: b) = gend  a                       &&   (any gend . take (gord (Proxy :: Proxy (f ())) `gcd` gord (Proxy :: Proxy (g ()))) . iterate grot) b
    gord  _        = gord (Proxy :: Proxy (f ())) `lcm` gord (Proxy :: Proxy (g ()))

instance (GCyclic f, GCyclic g) => GCyclic (f :+: g) where
    ggen        = L1 ggen
    grot (L1 a) = if gend a
                  then R1 (ggen)
                  else L1 (grot a)
    grot (R1 b) = if gend b
                  then L1 (ggen)
                  else R1 (grot b)
    gend (L1 _) = False
    gend (R1 b) = gend b
    gord  _     = gord (Proxy :: Proxy (f ())) + gord (Proxy :: Proxy (g ()))

Here are some more example instances:

-- Perfectly fine instances
instance Cyclic ()
instance Cyclic Bool
instance (Cyclic a, Cyclic b) => Cyclic (Either a b)

-- Not actually possible (the product of two arbitrary cycles is a cyclic group iff they are coprime)
instance (Cyclic a, Cyclic b) => Cyclic (a, b)

-- Doesn't have a finite order, doesn't seem to be a prime transfinite number.
-- instance (Cyclic a) => Cyclic [a]

And some example code to run:

typeOf :: a -> Proxy a
typeOf _ = Proxy

generate :: (Cyclic g) => Proxy g -> [g]
generate _ = go gen
    where
        go g = if end g
               then [g]
               else g : go (rot g)

main = do
    print . generate . typeOf $ A
    print . map rot . generate . typeOf $ A
    putStrLn []

    print . generate $ (Proxy :: Proxy (Either T3 Bool))
    print . map rot . generate $ (Proxy :: Proxy (Either T3 Bool))
    putStrLn []

    print . generate . typeOf $ (A, False)
    print . map rot . generate . typeOf $ (A, False)
    putStrLn []

    print . generate . typeOf $ (False, False)
    print . map rot . generate . typeOf $ (False, False)
    print . take 4 . iterate rot $ (False, True)
    putStrLn []

    print . generate $ (Proxy :: Proxy (Either () (Bool, Bool)))
    print . map rot . generate $ (Proxy :: Proxy (Either () (Bool, Bool)))
    print . take 8 . iterate rot $ (Right (False,True) :: Either () (Bool, Bool))
    putStrLn []

The fourth and fifth examples show off what's happening when we make an instance for the product of two cyclic groups whose orders are not coprime.

Seema answered 4/4, 2014 at 0:36 Comment(3)
Oops, I misunderstood what you're looking for. Yout gord was already supposed to be my gsize.Seema
What in particular are you not sure about in regards to products? The Cyclic instance for (:*:) is simple (if you know some basic algebra): f :*: g is equivalent to a direct product of cyclic groups f, g.Sculpsit
I figured it out when I put together ord == size and saw that you'd implemented it as lcm.Seema

© 2022 - 2024 — McMap. All rights reserved.