Search code examples
haskellhaskell-lens

How to lens onto field of a record which is a polymorphic function?


I just installed the lens library so I can easily set in a nested data structure. However, i ran into a problem. Here is a minimal example to demonstrate my problem

The following code doesn't compile:

{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
import Control.Lens    

data MyRecord = MyRecord 
  { _func :: forall . a -> a
  }

makeLenses ''MyRecord

changeMyRecord :: MyRecord -> MyRecord
changeMyRecord r = r & func .~ id

The error is No Instance for (Contravariant Identity) arising from use of 'func'.

I had a look at Contravariant, and I'm pretty sure that it is impossible for me to make this instance since

class Contravariant f where
  contramap :: (a -> b) -> f b -> f a

i.e. If f = \x -> x I don't see where i'm going to find something of type a to apply to the function argument (a-> b)

Is there a different way to modify a MyRecord using lenses? Or could I perhaps avoid RankNTypes somehow, but still pass around a polymorphic _func in my record? Or something else?

Record update syntax is off the cards - imagine that MyRecord is deeply nested.

Please assume very little haskell knowledge when answering, in particular I only started looking at the lens library today


Solution

  • lens is pulling a hack here – it wouldn't be possible to use func as a lens (or other write-capable optic) with type

    func :: Lens' MyRecord (a -> a)
    

    because that would mean you can put any concrete-type endofunction in, like

    changeMyRecord :: MyRecord -> MyRecord
    changeMyRecord r = r & func .~ ((+1) :: Int -> Int)
    

    So instead, it makes func only a getter

    func :: Getter' MyRecord (a -> a)
    

    ...which is ok, because a universal-polymorphic function can be used on any type, so the following works:

    useMyRecord :: MyRecord -> String
    useMyRecord r = show (r^.func $ 1 :: Int)
    

    And seeing that

    type Getter s a = ∀ f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s
    

    that's where that Contravariant constraint comes from. The No Instance for Contravariant error message is just VanLaarhoven-Kmett-ish for Can't use a ‘Getter’ as a ‘Setter’.

    What you'd actually want to have is of course

    func :: Lens' MyRecord (∀ a . a -> a)
    

    but that's unfortunately an impredicative type, which Haskell doesn't support. Namely, it would expand to

    func :: ∀ f . Functor f => ((∀ a . a -> a) -> f (∀ a . a -> a)) -> MyRecord -> f MyRecord
    

    Note that there's a inside the f.

    To get the semantics of such a polymorphic-field lens, you'll need to wrap that in a Rank-0 type:

    newtype PolyEndo = PolyEndo { getPolyEndo :: ∀ a . a -> a }
    
    data MyRecord = MyRecord 
      { _func :: PolyEndo
      }
    
    makeLenses ''MyRecord
    -- func :: Lens' MyRecord PolyEndo