Search code examples
haskellhaskell-lenstype-families

Writing classy lenses for records with type families?


Related to Lenses and TypeFamilies and How to derive instances for records with type-families and How to make lenses for records with type-families

Every time I've tried using type-families enthusiastically to reduce some boilerplate code, I've programmed myself into a corner. Here's the latest one -- how do I define a lens for RecordPoly f in the code snippet given below?

{-# LANGUAGE TemplateHaskell, DeriveGeneric, MultiParamTypeClasses, FunctionalDependencies, UndecidableInstances, DataKinds #-}
module Try where

import Control.Lens

data PGInt
data PGText

data Selector = Haskell | DB


type family DBField (f :: Selector) hask db where
  DBField 'Haskell hask _ = hask
  DBField 'DB _ db = db

data RecordPoly f = RecordPoly
  { recFieldA :: !(DBField f Int PGInt)
  , recFieldB :: !(DBField f String PGText)
  }

class HasFieldA s a | s -> a where fieldA :: Lens' s a

instance HasFieldA (RecordPoly 'Haskell) Int where
  fieldA fctor (RecordPoly fa fb) = fmap (\x -> RecordPoly x fb) (fctor fa)

It's failing with the following error:

• Illegal instance declaration for ‘HasFieldA (RecordPoly f) a’
    The liberal coverage condition fails in class ‘HasFieldA’
      for functional dependency: ‘s -> a’
    Reason: lhs type ‘RecordPoly f’ does not determine rhs type ‘a’
    Un-determined variable: a
• In the instance declaration for ‘HasFieldA (RecordPoly f) a’

The only thing that seems to work is the following:

instance HasFieldA (RecordPoly 'Haskell) Int where
  fieldA fctor (RecordPoly fa fb) = fmap (\x -> RecordPoly x fb) (fctor fa)

Is this the only way to make it work (thus resulting in a new kind of boilerplate explosion)? How come a similarly polymorphic version of this code works, but not when it is with type-families:

data RecordPoly fa fb = RecordPoly
  { recFieldA :: fa
  , recFieldB :: fb
  }

class HasFieldA s a | s -> a where fieldA :: Lens' s a

instance HasFieldA (RecordPoly fa fb) fa where
  fieldA fctor (RecordPoly fa fb) = fmap (\x -> RecordPoly x fb) (fctor fa)

Solution

  • Finally figured it out...

    instance (fa ~ DBField f Int PGInt) => HasFieldA (RecordPoly f) fa where
      fieldA fctor (RecordPoly fa fb) = fmap (\x -> RecordPoly x fb) (fctor fa)