我的getter和setter都可能失败,并带有描述如何操作的消息。因此,它们返回Either String
,这意味着我无法正常使用透镜。
考虑以下类型:
import qualified Data.Vector as V
data Tree a = Tree { label :: a
, children :: V.Vector (Tree a) }
type Path = [Int]
并非每个Path
到Tree
都会导致Tree
,因此吸气剂必须具有getSubtree :: Path -> Tree a -> Either String (Tree a)
之类的签名。设置者需要类似的签名(请参见下面的modSubtree
)。
如果getter和setter返回的类型为Tree a
,我将使用它们通过类似Lens.Micro中的lens
函数的方式创建一个镜头。但是,如果他们返回Either
,我就不能这样做。因此,我无法将它们与其他镜头组合在一起,因此必须进行大量包装和展开。
有什么更好的方法?
{-# LANGUAGE ScopedTypeVariables #-}
module I_wish_I_could_lens_this_Either where
import qualified Data.Vector as V
data Tree a = Tree { label :: a
, children :: V.Vector (Tree a) }
deriving (Show, Eq, Ord)
type Path = [Int]
-- | This is too complicated.
modSubtree :: forall a. Show a =>
Path -> (Tree a -> Tree a) -> Tree a -> Either String (Tree a)
modSubtree [] f t = Right $ f t
modSubtree (link:path) f t = do
if not $ inBounds (children t) link
then Left $ show link ++ "is out of bounds in " ++ show t
else Right ()
let (cs :: V.Vector (Tree a)) = children t
(c :: Tree a) = cs V.! link
c' <- modSubtree path f c
cs' <- let left = Left "imossible -- link inBounds already checked"
in maybe left Right $ modifyVectorAt link (const c') cs
Right $ t {children = cs'}
getSubtree :: Show a => Path -> Tree a -> Either String (Tree a)
getSubtree [] t = Right t
getSubtree (link:path) t =
if not $ inBounds (children t) link
then Left $ show link ++ "is out of bounds in " ++ show t
else getSubtree path $ children t V.! link
-- | check that an index into a vector is inbounds
inBounds :: V.Vector a -> Int -> Bool
inBounds v i = i >= 0 &&
i <= V.length v - 1
-- | Change the value at an index in a vector.
-- (Data.Vector.Mutable offers a better way.)
modifyVectorAt :: Int -> (a -> a) -> V.Vector a -> Maybe (V.Vector a)
modifyVectorAt i f v
| not $ inBounds v i = Nothing
| otherwise = Just ( before
V.++ V.singleton (f $ v V.! i)
V.++ after )
where before = V.take i v
after = V.reverse $ V.take remaining $ V.reverse v
where remaining = (V.length v - 1) - i
答案 0 :(得分:1)
您确实可以使用镜片做到这一点!或者更具体地说;遍历:)
首先进行一些设置:
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RankNTypes #-}
module TreeTraversal where
import qualified Data.Vector as V
import Control.Lens hiding (children)
data Tree a = Tree { _label :: a
, _children :: V.Vector (Tree a) }
deriving (Show, Eq, Ord, Functor)
makeLenses ''Tree
type Path = [Int]
从这一点开始,有两种方法可以进行:如果您只需要知道遍历是否成功(例如,路径中的任何链接都无法访问),则可以使用failover
;它需要一个遍历和一个函数,并会尝试在遍历上运行该函数,但是会在Alternative
上下文中返回结果;我们可以将此上下文选择为“也许”,以便我们可以通过模式匹配来检测失败并返回适当的Left
或Right
。我不知道遍历索引列表的简单方法,因此我写了一个快速助手来递归链接列表,并使用组合将它们转换为遍历。
modSubtreeWithGenericError
:: forall a. Show a
=> Path -> (Tree a -> Tree a) -> Tree a -> Either String (Tree a)
modSubtreeWithGenericError links f =
maybe (Left "out of bounds") Right . failover (pathOf links) f
where
pathOf :: [Int] -> Traversal' (Tree a) (Tree a)
pathOf [] = id
pathOf (p : ps) = children . ix p . pathOf ps
如果您只关心失败,那应该可以解决问题,但是很高兴知道失败在哪里吧?为此,我们可以编写一个自定义遍历,该遍历在Either String
中进行操作;大多数遍历必须在任何应用程序上进行,但是在我们的情况下,我们知道我们希望结果在Either中。因此我们可以利用它:
modSubtreeWithExpressiveError
:: forall a. Show a
=> [Int] -> (Tree a -> Tree a) -> Tree a -> Either String (Tree a)
modSubtreeWithExpressiveError links f = pathOf links %%~ (pure . f)
where
pathOf :: [Int] -> LensLike' (Either String) (Tree a) (Tree a)
pathOf [] = id
pathOf (x : xs) = childOrFail x . pathOf xs
childOrFail :: Show a => Int -> LensLike' (Either String) (Tree a) (Tree a)
childOrFail link f t =
if t & has (children . ix link)
then t & children . ix link %%~ f
else buildError link t
childOrFail
是有趣的一点; LensLike
位实际上只是(Tree a -> Either String (Tree a)) -> Tree a -> Either String (Tree a)
的别名,而traverse
专用于Either String
;但是,我们不能仅仅直接使用traverse
,因为我们只想遍历单个子树,并且我们的函数不仅在Tree a
上运行,而且在a
上运行。我手动编写了遍历,首先使用has
检查目标是否存在,然后以错误的错误Left
失败,或运行f
(代表遍历的其余部分) )使用%%~
覆盖适当的孩子。 %%~
组合器也有点吓人。具有讽刺意味的是,其定义实际上是(%%~) = id
;通常我们在这里使用%~
来代替;但它期望一个特定的Applicative与我们指定的Either String
不匹配。 %%~
可以愉快地运行我们的自定义遍历,尽管我们仍然需要在函数中添加一个额外的pure
才能使其进入Either上下文。
这是相当高级的镜头材料,但归根结底,这只是正常的遍历(大部分镜头)。
我这里有一个有关编写自己的遍历的指南,可能会对https://lens-by-example.chrispenner.ca/articles/traversals/writing-traversals
有帮助祝你好运!希望能有所帮助:)