haskell — any way to generate “deriving” instances for roughly-tuple-isomorphic data types?

StackOverflow https://stackoverflow.com//questions/9659919

  •  12-12-2019
  •  | 
  •  

Question

Suppose I have a data type like

data D a = D a a a

and a typeclass

class C c ...
instance (C c1, C c2) => C (c1, c2)

Then, I want to be able to write

data D a = D a a a deriving C

and have that generate an instance,

instance C ((a, a), a) => C (D a)

by using the modulo-lazy-evaluation isomorphism,

D a ~ ((a, a), a)

Note. Using a newtype and GeneralizedNewtypeDeriving will not work if, for example, one has data D m = D (m Integer) (m Integer).

Note 2. This question has relevance for Haskell expressiveness in general -- languages like Python have something called named tuples, which can be used anywhere tuples are used; this question shows where/how I don't know how to emulate the same thing in Haskell.

Was it helpful?

Solution

You can do this relatively cleanly and efficiently using GHC 7.4's generic programming support. The documentation for GHC.Generics may be helpful. Here's an example.

Consider the following example class and some sample instances:

class C a where
  -- | Double all numbers
  double :: a -> a

instance C Int where
  double i = 2 * i

instance (C a, C b) => C (a, b) where
  double (a, b) = (double a, double b)

We need some language pragmas and imports:

{-# LANGUAGE TypeOperators, DefaultSignatures, DeriveGeneric, FlexibleContexts, FlexibleInstances #-}
module Example where

import GHC.Generics hiding(C, D)

We now give some "generic instances". The generic types all have a phantom parameter x, which makes the instance heads a little more complicated:

-- "Insert" a normal value into a generic value
instance C c => C (K1 i c x) where
  double (K1 c) = K1 (double c)

-- Ignore meta-information (constructor names, type names, field names)
instance C (f x) => C (M1 i c f x) where
  double (M1 f) = M1 (double f)

-- Tuple-like instance
instance (C (f x), C (g x)) => C ((f :*: g) x) where
  double (f :*: g) = double f :*: double g

We now redefine our class C to take advantage of GC

class C a where
  -- | Double all numbers
  double :: a -> a

  -- specify the default implementation for double
  default double :: (Generic a, C (Rep a ())) => a -> a
  double = to0 . double . from0

-- from, with a more specialised type, to avoid ambiguity
from0 :: Generic a => a -> Rep a ()
from0 = from

-- to, with a more specialised type, to avoid ambiguity
to0 :: Generic a => Rep a () -> a
to0 = to

Now we can define some instances very easily:

data D a = D a a a deriving Generic
instance C a => C (D a)

data D2 m = D2 (m Int) (m Int) deriving Generic
instance C (D2 D)
Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top