Search code examples
haskelllenses

makeLenses on data with constraint (DatatypeContexts)


Can I use the makeLenses template on a data type with constraints and if so, how? I'd like to do so without reading all about Template Haskell.

In GHC I have this example:

{-# LANGUAGE TemplateHaskell, FlexibleInstances, UndecidableInstances, NoMonomorphismRestriction #-}
module Main (main) where

import Control.Lens
import Control.Monad.Reader  -- mtl

class Class1 a where
    someThing :: a  -- just some filler

instance (Num a) => Class1 a where
    someThing = 3

data (Class1 a) => Foo a = Foo { _field1 :: a }

makeLenses ''Foo

main :: IO ()
main = putStrLn . show $ runReader (view field1) $ Foo { _field1 = 5 }

This produces this compile error:

Could not deduce (Num a1) arising from a use of ‘Foo’
from the context (Profunctor p, Functor f)
  bound by the type signature for
             field1 :: (Profunctor p, Functor f) =>
                       p a (f a1) -> p (Foo a) (f (Foo a1))
  at src/main.hs:58:1-16
Possible fix:
  add (Num a1) to the context of
    the type signature for
      field1 :: (Profunctor p, Functor f) =>
                p a (f a1) -> p (Foo a) (f (Foo a1))
In the second argument of ‘iso’, namely ‘Foo’
In the expression: iso (\ (Foo x_a3NK) -> x_a3NK) Foo
In an equation for ‘field1’:
    field1 = iso (\ (Foo x_a3NK) -> x_a3NK) Foo

So I think it generated:

field1 :: Lens' (Foo a) a

I've also tried makeFields and makeClassy, to no avail.

I know I could work around this with:

field1 :: (Class1 a) => Lens' (Foo a) a
field1 = lens _field1 (\ foo val -> Foo { _field1 = val })

But is there a way to do it with makeLenses or Template Haskell?

I'm using GHC version 7.8.4, and lens version 4.8.

(Note: I know there have been similar questions about makeLenses, but I still couldn't get it to work. I'm a beginner at haskell.)


Solution

  • The problem, I believe, is that datatype contexts are a somewhat broken feature. You probably mean to use a GADT:

    {-# Language GADTs #-}
    
    data Foo a where
      Foo :: Class1 a => a -> Foo a
    

    I'm not sure how to get the record syntax in there with the class constraint.

    Unfortunately, as Ørjan Johansen commented, you will immediately run into trouble making the lenses automatically because of the existential type. But you should, I believe be able to write them by hand, whereas the datatype context would never ever have worked.