不使用 Template Haskell 的多态镜头

4

我正在尝试创建一个多态透镜声明(不使用模板哈斯克尔)来处理多个类型。

module Sample where
import Control.Lens
data A = A {_value:: Int}
data B = B {_value:: Int}
data C = C {_value:: String}
value = lens _value (\i x -> i{_value=x}) -- <<< ERROR

但是我收到了以下错误信息:
Ambiguous occurrence ‘_value’
It could refer to either the field ‘_value’,
                         defined at library/Sample.hs:5:13
                      or the field ‘_value’, defined at 
library/Sample.hs:4:13
                      or the field ‘_value’, defined at 
library/Sample.hs:3:13
  |
6 | value = lens _value (\i x -> i{_value=x}) -- <<< ERROR
  |              ^^^^^^

所以,目标是让 value 镜头适用于 A、B、C 三种类型。有没有办法实现这一点? 谢谢。

3个回答

10

使用generic-lens可以不使用 TH 派生镜头。您可以通过以下方式将通用field镜头专门化为特定字段并命名。

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeApplications #-}

import GHC.Generics (Generic)
import Control.Lens (Lens, (^.))
import Data.Generics.Product (HasField(field))

data A = A { _value :: Int } deriving Generic
data B = B { _value :: Int } deriving Generic
data C = C { _value :: String } deriving Generic

value :: HasField "_value" s t a b => Lens s t a b
value = field @"_value"

main :: IO ()
main = print (A 0 ^. value, B 0 ^. value, C "0" ^. value)

4

Haskell不支持像Java或C++这样的语言那样重载函数。为了实现您想要的功能,您需要使用一个类型类,例如:

class HasValue a b where
    value :: Lens' a b 

data A = A {_valueA:: Int}
data B = B {_valueB:: Int}
data C = C {_valueC:: String}

instance HasValue A Int where
   value = lens _valueA (\i x -> i{_valueA=x})

instance HasValue B Int where
   value = lens _valueB (\i x -> i{_valueB=x})

instance HasValue C String where
   value = lens _valueC (\i x -> i{_valueC=x}

你需要启用多参数类型类来完成这个任务。


1
你可能想让b函数依赖于a,即{-# LANGUAGE FunctionalDependencies #-} class HasValue a b | a -> b。或者,在我看来更好的方式是,将字段类型改为关联类型族:{-# LANGUAGE FunctionalDependencies #-} class HasValue a where {type ValueField a :: *; value :: Lens' a (ValueField a)} - leftaroundabout

0

如果你想避免DuplicateRecordFields,另一个选项是将每个字段定义在自己的模块中,但这需要使用限定导入才能将它们导入到同一模块中。

module Sample.A where
import Control.Lens
data A = A {_value:: Int}
value = lens _value (\i x -> i{_value=x})

module Sample.B where
import Control.Lens
data B = B {_value:: Int}
value = lens _value (\i x -> i{_value=x})

module Sample.C where
import Control.Lens
data C = C {_value:: String}
value = lens _value (\i x -> i{_value=x})

module Main where
import qualified Sample.A as A
import qualified Sample.B as B
import qualified Sample.C as C

main :: IO ()
main = print (A.A 0 ^. A.value, B.B 0 ^. B.value, C.C "0" ^. C.value)

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