Search code examples
haskellfunctorhaskell-lensunification

Is it impossible to let-bind a composite lens?


I'm having trouble understanding whether the following is feasible by helping the type-checker, or just outright impossible. The setup is slightly arbitrary, I just need some nested data types with lenses, here called A, B, C.

My problem is that I can use the composite lens (bLens . a) if I immediately call something like view using it, but if I try to let-bind it and give it a name, I get error messages.

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}

module Debug where

import Control.Eff
import Control.Eff.Reader.Strict
import Control.Lens

data A = A

data B = B
  { _a :: A
  }
makeLenses ''B

data C = C
  { _b :: B
  }
makeLenses ''C

askLensed :: ( Member (Reader r) e ) => Lens' r a -> Eff e a
askLensed l = view l <$> ask

works :: ( Member (Reader C) e ) => Lens' C B -> Eff e A
works bLens = do
  askLensed (bLens . a)

doesNotWork :: ( Member (Reader C) e ) => Lens' C B -> Eff e A
doesNotWork bLens = do
  let compositeLens = bLens . a
  askLensed compositeLens

doesNotWork2 :: ( Member (Reader C) e ) => Lens' C B -> Eff e A
doesNotWork2 bLens = do
  let compositeLens :: Lens' C A = bLens . a
  askLensed compositeLens

butThisIsFine :: Lens' C B -> Lens' C A
butThisIsFine bLens =
  let compositeLens = bLens . a in compositeLens

The error messages being:

• Could not deduce (Functor f0) arising from a use of ‘bLens’
  from the context: Member (Reader C) e
    bound by the type signature for:
               doesNotWork :: forall (e :: [* -> *]).
                              Member (Reader C) e =>
                              Lens' C B -> Eff e A
    at /home/.../.stack-work/intero/interoW51bOk-TEMP.hs:32:1-62
  The type variable ‘f0’ is ambiguous
  Relevant bindings include
    compositeLens :: (A -> f0 A) -> C -> f0 C

and:

• Couldn't match type ‘f0’ with ‘f’
    because type variable ‘f’ would escape its scope
  This (rigid, skolem) type variable is bound by
    a type expected by the context:
      Lens' C A
    at /home/.../.stack-work/intero/interoW51bOk-TEMP.hs:35:3-25
  Expected type: (A -> f A) -> C -> f C
    Actual type: (A -> f0 A) -> C -> f0 C
• In the first argument of ‘askLensed’, namely ‘compositeLens’
  In a stmt of a 'do' block: askLensed compositeLens
  In the expression:
    do let compositeLens = bLens . a
       askLensed compositeLens
• Relevant bindings include
    compositeLens :: (A -> f0 A) -> C -> f0 C

I have tried adding type signatures, with explicit quantification of the f and Functor constraints , but to no success so far.


Solution

  • A rule of thumb that simplifies many things is to not take Lens (or Lens', or Setter etc.) as function arguments unless you really need it the optic-polymorphism, but instead take the ALens (or ALens' or ASetter) version, which avoids the Rank-2 polymorphism issues.

    The problem is that if you give compositeLens a name in a do block, then it must have a type that can't be inferred from its context anymore. But Lens' C A is a polymorphic type under the hood, and this complicates type inferrence considerably. It is actually ok if you give an explicit signature:

    doesActuallyWork2 :: ( Member (Reader C) e ) => Lens' C B -> Eff e A
    doesActuallyWork2 bLens = do
      let compositeLens :: Lens' C A
          compositeLens = bLens . a
      askLensed compositeLens
    

    Your version doesNotWork2 didn't work because an definition with in-line signature is flipped over to the RHS, like

    doesNotWork2 :: ( Member (Reader C) e ) => Lens' C B -> Eff e A
    doesNotWork2 bLens = do
      let compositeLens = bLens . a :: Lens' C A
      askLensed compositeLens
    

    ...where compositeLens again tries to specialise the just-given type to one particular functor, which can't be done.

    The more straightforward solution is to avoid this local polymorphism entirely, which yout don't actually need: if you take an ALens' as the argument, the local binding automatically takes on the monomorphic type: like

    worksEasily :: ( Member (Reader C) e ) => ALens' C B -> Eff e A
    worksEasily bLens = do
      let compositeLens = bLens . a
      askLensed compositeLens
    

    Actually not quite this; it turns out you don't want ALens' here but Getting. The easiest way to find this out it to remove the signature to askLensed and let the compiler tell you what it infers, then work backwards from that.

    askLensed :: ( Member (Reader r) e ) => Getting a r a -> Eff e a
    askLensed l = view l <$> ask
    
    worksEasily :: ( Member (Reader r) e ) => Getting A r B -> Eff e A
    worksEasily bLens = do
      let compositeLens = bLens . a
      askLensed compositeLens