如何将 iset 与嵌套数据类型和镜头一起使用?

How to use iset with nested datatype and lenses?

我无法让最后一个函数中的类型对齐。要点是将所有价格双打与仅取决于 3 元组索引的函数相关联。元组中原来的Double值可以舍弃

{-# LANGUAGE TemplateHaskell   #-}
{-# LANGUAGE TupleSections #-}

import Control.Lens

data Typex = Typex 
    { _level       :: Int
    , _coordinate  :: (Int, Int)
    , _connections :: [(Int, (Int, Int), Double)]  -- = (level, coordinate, price)
    } deriving Show
makeLenses ''Typex

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

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

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

setInitPrices  :: [[Typex]] -> [[Typex]]
setInitPrices  (x:rest) = map setIndexPrices x : setInitPrices  rest
  where setIndexPrices :: Typex -> Typex
        setIndexPrices tx =  n & connections .~ ??? -- using iset (?), set the price in every 3-tuple so that price = f (index of the 3-tuple) where f = i*2
setInitPrices  lst = lst

您可能正在寻找:

  where setIndexPrices :: Typex -> Typex
        setIndexPrices tx =  tx & connections .> traversed <. _3 .@~ f
        f i = 2 * fromIntegral i

这里,.@~iset的运算符版本,.><.是组合运算符.的变体,用于组合索引光学.

如果考虑更简单的无索引光学器件:

connections . traverse . _3

这个optical取一个TypeX,关注它的_connections字段,遍历连接列表,关注每个连接的第三个字段(价格)。结果是一个光学器件按顺序遍历 TypeX 中的所有价格。

要索引这个光学元件,我们需要 "upgrade" 未索引的 traverse 到索引的 traversed。然后,我们要使用保留索引的合成运算符 .><.,其中 less/greater 符号指向具有我们想要的索引的光学器件部分。 (在具有多个索引的更复杂的场景中,您可以使用 <.> 将来自两个光学器件的索引组合成索引对 (i,j)。)

我们就是这样得到的:

connections .> traversed <. _3

还是按顺序遍历了TypeX中的所有价格,但是也带着遍历出来的索引

请注意,setInitPrices 实际上是可以轻松编写为 "all at once" 镜头计算的函数之一。 map setIndexPrices 和递归只是遍历嵌套列表,所以它们等同于光学 traverse . traverse。所以,我们可以使用:

setInitPrices' :: [[Typex]] -> [[Typex]]
setInitPrices' = traverse .> traverse .> connections .> traversed <. _3 .@~ f
  where f i = 2 * fromIntegral i

最后,可能值得注意的是,如果您有一个复杂的索引光学器件,例如:

a .> b .> c .> d <. e <. f <. g

出于不明确的原因(运算符的右结合性以及 .>. 相同的事实)这始终等同于:

a . b . c .> d <. e . f . g

这是比较常见的写法。因此,setInitPrices' 的最终版本将是:

setInitPrices' :: [[Typex]] -> [[Typex]]
setInitPrices' = traverse . traverse . connections .> traversed <. _3 .@~ f
  where f i = 2 * fromIntegral i