Another Lens Optics type difference

I’m working through the Servant tutorial using genericServeTWithContext to serve an endpoint that’s serving a JWKSet as JSON along the lines of this guide Hoist Server With Context for Custom Monads — Servant documentation

jwksServe :: ReaderT Env Handler JWKSet
jwksServe = do
  t <- asks getJwks
  pure $ jwksPub t

jwksPub :: JWKSet -> JWKSet
jwksPub (JWKSet a) = do               -- `a` here is [JWK]
  let pks = mapM (view asPublicKey) a -- Succeeds with `view` from Lens
  case pks of
    Just x -> JWKSet x
    Nothing -> JWKSet []

However if I use Optics with

  let pks = mapM (view (lensVL asPublicKey)) a -- Fails with `view` from Optics

I get the following error leaving me stumped

   • Could not deduce ‘Data.Functor.Contravariant.Contravariant f’
        arising from a use of ‘asPublicKey’
      from the context: Functor f
        bound by a type expected by the context:
                   LensVL JWK JWK (Maybe JWK) (Maybe JWK)
        at src/Server.hs:189:32-42
      Possible fix:
        add (Data.Functor.Contravariant.Contravariant f) to the context of
          a type expected by the context:
            LensVL JWK JWK (Maybe JWK) (Maybe JWK)
    • In the first argument of ‘lensVL’, namely ‘asPublicKey’
      In the first argument of ‘view’, namely ‘(lensVL asPublicKey)’
      In the first argument of ‘mapM’, namely
        ‘(view (lensVL asPublicKey))’
    |
189 |   let pks = mapM (view (lensVL asPublicKey)) a -- Fails with Optics
    |                                ^^^^^^^^^^^
1 Like

The reason that this doesn’t work is that asPublicKey is a Getter not a Lens. You really need getterVL for this, but it doesn’t exist. I don’t know why not, so I opened an issue.

In the meantime maybe you could just paste the definition into your project:

-- | Type synonym for a van Laarhoven getter.
type GetterVL s a =
  forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s

-- | Build a getter from the van Laarhoven representation.
getterVL :: GetterVL s a -> Getter s a
getterVL g = Optic (getting g)

getting :: (Profunctor p, Bicontravariant p) => ((s -> Const s s) -> a -> Const s a) -> p i s c1 -> p i a c2
getting g = lmap (getConst . g Const) . rphantom

(for rphantom you’ll need to import Optics.Internal.Bi)

3 Likes

That worked perfectly, thanks. Tested with ghc 9.12

1 Like