首页 > 解决方案 > 当修改依赖于索引时,如何使用镜头修改嵌套自定义数据类型的字段

问题描述

考虑到以下几点:

{-# LANGUAGE TemplateHaskell   #-}

import Control.Lens

data Typex = Typex 
    { _level       :: Int
    , _coordinate  :: (Int, Int)
    , _connections :: [(Int,(Int,Int))]
    } deriving Show
makeLenses ''Typex

initTypexLevel :: Int -> Int -> Int -> [Typex] 
initTypexLevel a b c = [ Typex a (x, y) [(0,(0,0))]
                       | x <- [0..b], y <- [0..c]
                       ]

buildNestedTypexs :: [(Int, Int)] -> [[Typex]]
buildNestedTypexs pts
     = setConnections [ initTypexLevel i y y
                      | (i,(_,y)) <- zip [0..] pts
                      ]

setConnections :: [[Typex]] -> [[Typex]]
setConnections = ?

我如何使用镜头来修改connectionsin allTypex具有类型功能的所有 s,[[Typex]] -> [[Typex]]使得在每个Typex

connections = [(level of Typex being modified +1, (x, y))] where
x,y = 0..(length of next [Typex] in [[Typex]])/2

X 和 y 都需要经过下一个 [Typex] 的那个长度。如果可能,最终的 [Typex] 应保持不变。所以同一个[Typex]中每个Typex的所有连接都是一样的。

的输出setConnections $ buildNestedTypexs [(0,1),(1,1)]应该是:

[ [ Typex { _level = 0
          , _coordinate = (0,0)
          , _connections = [(1,(0,0)), (1,(0,1)), (1,(1,0)), (1,(1,1))] }
  , Typex { _level = 0
          , _coordinate = (0,1)
          , _connections = [(1,(0,0)), (1,(0,1)), (1,(1,0)), (1,(1,1))] }
  , Typex { _level = 0
          , _coordinate = (1,0)
          , _connections = [(1,(0,0)), (1,(0,1)), (1,(1,0)), (1,(1,1))] }
  , Typex { _level = 0
          , _coordinate = (1,1)
          , _connections = [(1,(0,0)), (1,(0,1)), (1,(1,0)), (1,(1,1))] }
  ]
 ,[ Typex { _level = 1
          , _coordinate = (0,0)
          , _connections = [(0,(0,0))] }
  , Typex { _level = 1
          , _coordinate = (0,1)
          , _connections = [(0,(0,0))] }
  , Typex { _level = 1
          , _coordinate = (1,0)
          , _connections = [(0,(0,0))] }
  , Typex { _level = 1
          , _coordinate = (1,1)
          , _connections = [(0,(0,0))] }
  ]]

我想我需要,import Control.Lens.Indexed但仅此而已,因此感谢所有帮助。

标签: haskellnestedindiceshaskell-lenscustom-data-type

解决方案


这是你想要的吗?

{-# LANGUAGE TupleSections #-}

setConnections :: [[Typex]] -> [[Typex]]
setConnections (x:rest@(y:_)) = map (connect y) x : setConnections rest
  where connect :: [Typex] -> Typex -> Typex
        connect txs tx
          = tx & connections .~ (map ((tx ^. level) + 1,) $ txs ^.. traverse.coordinate)
setConnections lst = lst

这不是一个纯粹的镜头解决方案,但我发现作为一般规则使用镜头时,让镜头完成所有工作并不总是一个好主意。它只会让事情变得难以编写和理解。

在这里,我在很多地方都使用了“plain Haskell”:使用手动递归进行模式匹配以处理对连续的 s x,我已经习惯了第一个和第二个。我还习惯将新级别添加到坐标列表以生成新值。y[Typex]mapconnectTypexx :: [Typex]y :: [Typex]mapconnections

这里使用的唯一镜头表达式是:

  • tx & connections .~ (...)用新值替换connections字段tx :: Typex
  • tx ^. level它获取当前的级别tx :: Typex
  • txs ^.. traverse.coordinate它获取列表coordinate中所有Typex值的字段txs :: [Typex]并将它们作为列表返回[(Int,Int)]

在我看来,镜头和“普通 Haskell”之间的这种平衡是处理复杂变换的最佳方式。


推荐阅读