Search code examples
haskellderiving

Derive instance from field in record


Example code:

{-# LANGUAGE NamedFieldPuns #-}

module Sample where

class Sample a where
  isA :: a -> Bool
  isB :: a -> Bool
  isC :: a -> Bool

data X =
  X

instance Sample X where
  isA = undefined
  isB = undefined
  isC = undefined

data Wrapper = Wrapper
  { x :: X
  , i :: Int
  }

instance Sample Wrapper where
  isA Wrapper {x} = isA x
  isB Wrapper {x} = isB x
  isC Wrapper {x} = isC x

Here, I have some class that is implemented by X, and then another record Wrapper containing X.

I want Wrapper to derive the Sample instance, through its field x.

I know I can do so by getting the field and calling it myself for each function, as shown.

Is there some flag or some method to do so automatically or once only?

This seems similar to DerivingVia and GeneralisedNewtypeDeriving, but both seem to target newtype or coercible types only


Solution

  • Here are some strategies that do not require any extensions, but trade some upfront cost for the ease of deriving these classes.

    Note that since Sample is not a newtype, there's no guarantee it will only hold one X and not two, more or a variable amount (Maybe X? Either X X?). Therefore, as you'll see, your options have to make the choice of X inside the structure explicit, and that is a likely reason for an extension that derives this automatically to not exist.

    Derive one function instead of many

    To satisfy Sample, we really need an X. Let's make that a typeclass:

    class HasX t where
      getX :: t -> X
    
    class Sample t where
      isA :: t -> Bool
      isB :: t -> Bool
      isC :: t -> Bool
      default isA :: HasX t => t -> Bool
      isA = isA . getX
      default isB :: HasX t => t -> Bool
      isB = isB . getX
      default isC :: HasX t => t -> Bool
      isC = isC . getX
    
    instance HasX Wrapper where
      getX = x
    
    instance Sample Wrapper -- no implementation necessary
    

    Derive via generics

    Let's say we want to only work on the records that have X as the first field. To match the type structure, we can use GHC.Generics. Here we add a way for HasX to default to the first field:

    class HasX t where
      getX :: t -> X
      default getX :: (Generic a, HasX (Rep a)) => t -> X
      getX = getX . from
    
    instance HasX (M1 D d (M1 C c (M1 S s (Rec0 X) :*: ff))) o where
      getX (M1 (M1 ((M1 (K1 x)) :*: _))) = x
    

    The last instance for HasX matches any record (M1 D) with a single constructor (M1 C), which has more than one (:*:) field (M1 S), the first field being of type (Rec0) X.

    (Yes, the generic instance is unwieldy. Edits welcome.)

    (To see the exact representation of the generic type of Wrapper, inspect Rep Wrapper in the GHCi console.)

    Now the instance for Wrapper can be written as:

    data Wrapper = Wrapper
      { x :: X
      , i :: Int
      }
      deriving (Generic, HasX, Sample)