如何将镜头(或任何其他光学元件)同时作为getter和setter来处理?

3
我正试图编写一个通用的记录更新器,它将使您能够轻松地更新现有记录中的字段,并使用形状相似的传入记录中的字段。以下是我目前的代码:
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

我希望以以下方式使用它:

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}

这个不起作用,可能是因为Haskell为applyUpdater推断出了一个非常奇怪的类型签名,这意味着它没有做我期望的事情:

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

以下是代码示例和编译错误:

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

编译错误:

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)
2个回答

6
首先要注意的是,(^.) 将镜头作为其参数,因此您实际想要的是 getters = DL.map (flip (^.)) fields,也就是 DL.map view field
但更有趣的问题在于:光学工具需要高阶多态性,因此 GHC 只能猜测类型。出于这个原因,始终从类型签名开始
天真地说,您可能会写成:
applyUpdater :: [Lens' s a] -> s -> s -> s

这实际上是不可行的,因为Lens'包含一个量词,所以将其放入列表中需要使用非预测多态,而 GHC 实际上并不支持。这是一个常见的问题,因此 lens 库有两种解决方法:

  • 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现在将按照我使用ALens'的方式工作,但它只能用于一个聚焦于相同类型字段的镜头列表。将聚焦于不同类型字段的镜头放入列表中显然是一种类型错误。为了实现这一点,您必须将镜头包装在某个新类型中以隐藏类型参数 - 没有办法绕过它,将emailnotificationEnabled的类型统一到可以放入单个列表中的类型是不可能的。

但在经历这些麻烦之前,我强烈建议您根本不要将任何镜头存储在列表中:基本上只需要组合所有访问共享引用的更新函数。好吧,直接这样做 - “所有访问共享引用”恰好是函数单子提供给您的,因此编写起来非常简单。

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

将镜头转换为单独的更新器函数,可以这样编写:

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

可以像这样使用

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

你的代码还有另一个问题,即你部分应用了 ^.^#,但是顺序错了。使用 DL.map (flip (^#)) fields 能否解决这个问题? - leftaroundabout
嗯,你想把不同类型的字段放到一个列表中并使用镜头进行操作?这样做失败了也不应该让你感到意外,对吧? - leftaroundabout
这个能不能用元组来实现呢?比如 applyUpdater2applyUpdater3applyUpdater4 等等? - Saurabh Nanda
似乎使用元组可以工作。您知道如何使此代码更短吗?applyUpdater2 (f1, f2) existing incoming = (storing f2 (incoming ^# f2)) $ (storing f1 (incoming ^# f1) existing) - Saurabh Nanda
好吧...使用更短的变量名?但是,我认为将这些内容包装在固定长度的元组中并不明智。请使用列表,但仅存储不再提及更新元素类型的具体更新程序形式。 - leftaroundabout
显示剩余2条评论

0

根据@leftaroundabout的回答,还有一种基于元组的方法:

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

可以按照以下方式使用:

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

设置applyUpdaterN直到32元组应该足够容易。之后,一切都归结于个人偏好和实际用例。您可能希望不必在每个调用站点上使用mkUpd包装更新程序。另一方面,如果您想动态生成updaters列表,则使用列表比使用元组更容易。


网页内容由stack overflow 提供, 点击上面的
可以查看英文原文,
原文链接