在我的应用程序中,我正在尝试实现动画系统。在此系统中,动画表示为帧的循环列表:

data CyclicList a = CL a [a]

我们可以(低效地)推进动画,如下所示:
advance :: CyclicList a -> CyclicList a
advance (CL x []) = CL x []
advance (CL x (z:zs)) = CL z (zs ++ [x])

现在,我非常确定此数据类型是普通的:
instance Functor CyclicList where
  fmap f (CL x xs) = CL (f x) (map f xs)

cyclicFromList :: [a] -> CyclicList a
cyclicFromList [] = error "Cyclic list must have one element!"
cyclicFromList (x:xs) = CL x xs

cyclicLength :: CyclicList a -> Int
cyclicLength (CL _ xs) = length xs + 1

listCycles :: CyclicList a -> [CyclicList a]
listCycles cl = let
  helper 0 _ = []
  helper n cl' = cl' : (helper (n-1) $ advance cl')
 in helper (cyclicLength cl) cl

instance Comonad CyclicList where
  extract (CL x _) = x
  duplicate = cyclicFromList . listCycles

我的问题是:使用comonad实例可以获得什么好处(如果有)?

最佳答案

提供类型类或实现接口(interface)的优点是,编写为使用该类型类或接口(interface)编写的代码可以使用您的代码而无需进行任何修改。

可以使用Comonad编写哪些程序? Comonad提供了一种使用extract来检查当前位置的值(不观察其邻居)的方法,以及一种使用duplicateextend观察每个位置的邻域的方法。没有任何其他功能,这并不是非常有用。但是,如果我们还需要其他功能以及Comonad实例,则可以编写依赖于本地数据和其他位置的数据的程序。例如,如果我们需要允许我们更改位置的函数(例如advance),我们可以编写仅依赖于数据的本地结构而不依赖于数据结构本身的程序。

举一个具体的例子,考虑一个根据Comonad和以下Bidirectional类编写的元胞自动机程序:

class Bidirectional c where
    forward  :: c a -> Maybe (c a)
    backward :: c a -> Maybe (c a)

该程序可以将其与Comonad一起用于存储在单元格中的extract数据,并浏览当前单元格的forwardbackward单元。它可以使用duplicate捕获每个单元格的邻域,并使用fmap检查该邻域。 fmap f . duplicate的这种组合是extract f

这是这样的程序。 rule'仅对示例很有趣;它仅使用左右值在邻域上实现了元胞自动机规则。 rule在给定类的情况下从邻居中提取数据,并在每个邻居上运行规则。 slice会拉出更大的邻域,以便我们可以轻松地显示它们。 simulate运行模拟,为每一代显示这些较大的邻域。
rule' :: Word8 -> Bool -> Bool -> Bool -> Bool
rule' x l m r = testBit x ((if l then 4 else 0) .|. (if m then 2 else 0) .|. (if r then 1 else 0))

rule :: (Comonad w, Bidirectional w) => Word8 -> w Bool -> w Bool
rule x = extend go
    where
        go w = rule' x (maybe False extract . backward $ w) (extract w) (maybe False extract . forward $ w)

slice :: (Comonad w, Bidirectional w) => Int -> Int -> a -> w a -> [a]
slice l r a w = sliceL l w (extract w : sliceR r w)
    where
        sliceR r w | r > 0 = case (forward w) of
            Nothing -> take r (repeat a)
            Just w' -> extract w' : sliceR (r-1) w'
        sliceR _ _ = []
        sliceL l w r | l > 0 = case (backward w) of
            Nothing -> take l (repeat a) ++ r
            Just w' -> sliceL (l-1) w' (extract w':r)
        sliceL _ _ r = r

simulate :: (Comonad w, Bidirectional w) => (w Bool -> w Bool) -> Int -> Int -> Int -> w Bool -> IO ()
simulate f l r x w = mapM_ putStrLn . map (map (\x -> if x then '1' else '0') . slice l r False) . take x . iterate f $ w

该程序可能打算与列表中的以下Bidirectional Comonad一起使用。
data Zipper a = Zipper {
    heads :: [a],
    here  :: a,
    tail  :: [a]
} deriving Functor

instance Bidirectional Zipper where
    forward (Zipper _ _ []    ) = Nothing
    forward (Zipper l h (r:rs)) = Just $ Zipper (h:l) r rs
    backward (Zipper []     _ _) = Nothing
    backward (Zipper (l:ls) h r) = Just $ Zipper ls l (h:r)

instance Comonad Zipper where
    extract = here
    duplicate (Zipper l h r) = Zipper (goL (h:r) l) (Zipper l h r) (goR (h:l) r)
        where
            goL r []    = []
            goL r (h:l) = Zipper l h r : goL (h:r) l
            goR l []    = []
            goR l (h:r) = Zipper l h r : goR (h:l) r

但也可以与Zipper CyclicList Bidirectional一起使用。
data CyclicList a = CL a (Seq a)
    deriving (Show, Eq, Functor)

instance Bidirectional CyclicList where
    forward (CL x xs) = Just $ case viewl xs of
        EmptyL    -> CL x xs
        x' :< xs' -> CL x' (xs' |> x)
    backward (CL x xs) = Just $ case viewr xs of
        EmptyR    -> CL x xs
        xs' :> x' -> CL x' (x <| xs')

instance Comonad CyclicList where
    extract   (CL x _) = x
    duplicate (CL x xs) = CL (CL x xs) (go (singleton x) xs)
        where
            go old new = case viewl new of
                EmptyL -> empty
                x' :< xs' -> CL x' (xs' >< old) <| go (old |> x') xs'

我们可以将Comonad与任何一种数据结构一起重用。 simulate具有更有趣的输出,因为它不会撞到墙,而是会回绕以与自身交互。
{-# LANGUAGE DeriveFunctor #-}

import Control.Comonad
import Data.Sequence hiding (take)
import Data.Bits
import Data.Word

main = do
    putStrLn "10 + 1 + 10 Zipper"
    simulate (rule 110) 10 10 30 $ Zipper (take 10 . repeat $ False) True (take 10 . repeat $ False)
    putStrLn "10 + 1 + 10 Cyclic"
    simulate (rule 110) 10 10 30 $ CL True (fromList (take 20 . repeat $ False))

10-08 04:32