How to treat a lens (or any other optic) as a getter and setter simultaneously?

落爺英雄遲暮 提交于 2019-12-13 17:13:45

问题


I'm trying to write a generic record updater which will allow one to easily update fields in an existing record, with fields in a similarly shaped incoming record. Here is what I have till now:

applyUpdater fields existing incoming =
  let getters = DL.map (^.) fields
      setters = DL.map set fields
      updaters = DL.zipWith (,) getters setters
  in DL.foldl' (\updated (getter, setter) -> setter (getter incoming) updated) existing updaters

And I wish to use it in the following manner:

applyUpdater 
  [email, notificationEnabled] -- the fields to be copied from incoming => existing (this obviously assumed that `name` and `email` lenses have already been setup
  User{name="saurabh", email="blah@blah.com", notificationEnabled=True}
  User{name="saurabh", email="foo@bar.com", notificationEnabled=False}

This doesn't work, probably because Haskell infers a very weird type signature for applyUpdater which means it it not doing what I'm expecting it to do:

applyUpdater :: [ASetter t1 t1 a t] -> t1 -> Getting t (ASetter t1 t1 a t) t -> t1

Here's a code-sample and the compile error:

module TryUpdater where
import Control.Lens
import GHC.Generics
import Data.List as DL

data User = User {_name::String, _email::String, _notificationEnabled::Bool} deriving (Eq, Show, Generic)
makeLensesWith classUnderscoreNoPrefixFields ''User

-- applyUpdater :: [ASetter t1 t1 a t] -> t1 -> Getting t (ASetter t1 t1 a t) t -> t1
applyUpdater fields existing incoming =
  let getters = DL.map (^.) fields
      setters = DL.map set fields
      updaters = DL.zipWith (,) getters setters
  in DL.foldl' (\updated (getter, setter) -> setter (getter incoming) updated) existing updaters

testUpdater :: User -> User -> User
testUpdater existingUser incomingUser = applyUpdater [email, notificationEnabled] existingUser incomingUser

Compile error:

18  62 error           error:
 • Couldn't match type ‘Bool’ with ‘[Char]’
     arising from a functional dependency between:
       constraint ‘HasNotificationEnabled User String’
         arising from a use of ‘notificationEnabled’
       instance ‘HasNotificationEnabled User Bool’
         at /Users/saurabhnanda/projects/vl-haskell/.stack-work/intero/intero54587Sfx.hs:8:1-51
 • In the expression: notificationEnabled
   In the first argument of ‘applyUpdater’, namely
     ‘[email, notificationEnabled]’
   In the expression:
     applyUpdater [email, notificationEnabled] existingUser incomingUser (intero)
18  96 error           error:
 • Couldn't match type ‘User’
                  with ‘(String -> Const String String)
                        -> ASetter User User String String
                        -> Const String (ASetter User User String String)’
   Expected type: Getting
                    String (ASetter User User String String) String
     Actual type: User
 • In the third argument of ‘applyUpdater’, namely ‘incomingUser’
   In the expression:
     applyUpdater [email, notificationEnabled] existingUser incomingUser
   In an equation for ‘testUpdater’:
       testUpdater existingUser incomingUser
         = applyUpdater
             [email, notificationEnabled] existingUser incomingUser (intero)

回答1:


First, note that (^.) takes the lens as its right argument, so what you really want is actually getters = DL.map (flip (^.)) fields, aka DL.map view field.

But the more interesting problem here: optics require higher-rank polymorphism, so GHC can only guess types. Always start out with the type signature for this reason!

Naïvely, you would probably write

applyUpdater :: [Lens' s a] -> s -> s -> s

Well, that doesn't actually work, because Lens' includes a quantifier so putting it in a list would require impredicative polymorphism, which GHC isn't really capable of. Common problem, so the lens library has two ways of getting around that:

  • ALens is just a specific instantiation of the Functor constraint, chosen so you retain the full generality. You need to use different combinators for applying it, however.

    applyUpdater :: [ALens' s a] -> s -> s -> s
    applyUpdater fields existing incoming =
     let getters = DL.map (flip (^#)) fields
         setters = DL.map storing fields
         updaters = DL.zipWith (,) getters setters
     in DL.foldl' (\upd (γ, σ) -> σ (γ incoming) upd) existing updaters
    

    Because ALens is strictly an instantiation of Lens, you can use that exactly the way you intended.

  • ReifiedLens keeps the original polymorphism, but wraps it in a newtype so the lenses can be stored in e.g. a list. The wrapped lens can then be used as usual, but you'll need to explicitly wrap them to pass into your function; this is probably not worth the hassle for your application. This approach is more useful when you want to re-use the stored lenses in a less direct manner. (This can also be done with ALens, but it requires cloneLens which I reckon is bad for performance.)

applyUpdater will now work the way I explained with ALens', however it can only be used with a lists of lenses all focusing of fields of the same type. Putting lenses focusing on fields of different type in a list is quite clearly a type error. To accomplish that, you must wrap the lenses in some newtype to hide the type parameter – no way around it, it's simply not possible to unify the types of email and notificationEnabled to something you can stuff in one single list.

But before going through that trouble, I would strongly consider not storing any lenses in a list at all: basically what is just composing update-functions that all access a shared reference. Well, do that directly – “all accessing a shared reference” is, conveniently, exactly what the function monad offers you, so it's trivial to write

applyUpdater :: [s -> r -> s] -> s -> r -> s
applyUpdater = foldr (>=>) pure

To convert a lens to an individual updater-function, write

mkUpd :: ALens' s a -> s -> s -> s
mkUpd l exi inc = storing l (inc^#l) exi

to be used like

applyUpdater 
  [mkUpd email, mkUpd notificationEnabled]
  User{name="saurabh", email="blah@blah.com", notificationEnabled=True}
  User{name="saurabh", email="foo@bar.com", notificationEnabled=False}



回答2:


Based off @leftaroundabout 's answer, there's an approach based on tuples as well:

applyUpdater2 (f1, f2) existing incoming = (storing f2 (incoming ^# f2)) $ (storing f1 (incoming ^# f1) existing)
applyUpdater3 (f1, f2, f3) existing incoming = (storing f3 (incoming ^# f3)) $ (applyUpdater2 (f1, f2) existing incoming)
applyUpdater4 (f1, f2, f3, f4) existing incoming = (storing f4 (incoming ^# f4)) $ (applyUpdater3 (f1, f2, f3) existing incoming)
-- and so on

Which can be used in the following manner:

testUpdater :: User -> User -> User
testUpdater existingUser incomingUser = applyUpdater2 (email, notificationEnabled) existingUser incomingUser

Setting up applyUpdaterN till, say 32-tuples, should be easy enough. After that, it all boils down to personal preference and actual use-cases. You may prefer not having to wrap your updaters with mkUpd at every call site. On the other hand, if you want to generate the updaters list dynamically, then working with lists is easier than working with tuples.



来源:https://stackoverflow.com/questions/45618101/how-to-treat-a-lens-or-any-other-optic-as-a-getter-and-setter-simultaneously

标签
易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!