键入已经是Functor?

仍在编辑我的文本编辑器Rasa。

目前我正在构建跟踪视口/分割的系统(类似于vim分割)。 我很自然地把这个结构表示为一棵树:

data Dir = Hor
         | Vert
         deriving (Show)

data Window a =
  Split Dir SplitInfo (Window a) (Window a)
    | Single ViewInfo a
    deriving (Show, Functor, Traversable, Foldable)

这很好,我把我的View存储在树中,然后我可以遍历/ fmap来改变它们,它也与镜头包很好地吻合!

我最近一直在学习递归方案,因为树是一个递归数据结构,所以对他们来说这似乎是一个合适的用例。

我设法弄清楚了构建Fixpoint版本的好处:

data WindowF a r =
  Split Dir SplitInfo r r
    | Single ViewInfo a
    deriving (Show, Functor)

type Window a = Fix (WindowF a)

但是,现在的Functor实例已经被r用完了。

我已经尝试了一些变体

deriving instance Functor Window

但它窒息,因为窗口是一个类型的同义词。

和:

newtype Window a = Window (Fix (WindowF a)) deriving Functor

而且这也失败了。

• Couldn't match kind ‘* -> *’ with ‘*’
    arising from the first field of ‘Window’ (type ‘Fix (WindowF a)’)
• When deriving the instance for (Functor Window)
  • 是否仍然可以定义fmap /遍历a ? 还是我需要使用递归方案原语来完成这些操作? 我是否实施Bifunctor? 实例实现看起来像什么?
  • 其余的类型在这里,项目不编译,因为我没有窗口的适当的Functor实例...

    谢谢!!


    是的,您想使用Data.Bifunctor.FixFix版本:

    newtype Fix p a = In { out :: p (Fix p a) a }
    
    instance Bifunctor p => Functor (Fix p) where
      fmap f (In x) = In (bimap (fmap f) f x)
    

    你必须改变你的WindowF类型以匹配:

    data WindowF r a =
      Split Dir SplitInfo r r
        | Single ViewInfo a
        deriving (Show, Functor)
    
    instance Bifunctor WindowF where
      bimap f _g (Split dir si x y) = Split dir si (f x) (f y)
      bimap _f g (Single vi a) = Single vi (g a)
    
    newtype Window a = Window (Fix WindowF a) deriving Functor
    

    有可能对此使用recursion-schemes ,以及一个辅助类型:

    import Data.Functor.Foldable hiding (Fix (..))
    import Data.Profunctor.Unsafe
    import Data.Coerce
    
    newtype Flip p a b = Flip {unFlip :: p b a}
    
    instance Bifunctor p => Bifunctor (Flip p) where
      bimap f g (Flip x) = Flip (bimap g f x)
    
    instance Bifunctor p => Functor (Flip p a) where
      fmap = coerce (first :: (x -> y) -> p x a -> p y a)
        :: forall x y . (x -> y) -> Flip p a x -> Flip p a y
    
    type instance Base (Fix p a) = Flip p a
    instance Bifunctor p => Recursive (Fix p a) where
      project = Flip #. out
      cata f = f . Flip . first (cata f) . out
    

    不幸的是,为newtype-wrapped版本定义Recursive有点棘手:

    newtype Window a = Window {getWindow :: Fix WindowF a} deriving (Functor)
    type instance Base (Window a) = Flip WindowF a
    
    instance Recursive (Window a) where
      project = coerce #. project .# getWindow
      cata = (. getWindow) #. cata
    

    经过大量的摔跤之后,我得出结论:更好的选择是定义两种数据类型; 一个具有所需属性(在本例中为Bifunctor)的标准数据类型和一个可为其定义BaseRecursiveCorecursive实例的递归Functor数据类型。

    这是它的样子:

    {-# language DeriveFunctor, DeriveTraversable, TypeFamilies  #-}
    
    import Data.Typeable
    import Data.Bifunctor
    import Data.Functor.Foldable
    
    data BiTree b l =
      Branch b (BiTree b l) (BiTree b l)
        | Leaf l
        deriving (Show, Typeable, Functor, Traversable, Foldable)
    
    instance Bifunctor BiTree where
      bimap _ g (Leaf x) = Leaf (g x)
      bimap f g (Branch b l r) = Branch (f b) (bimap f g l) (bimap f g r)
    
    data BiTreeF b l r =
      BranchF b r r
        | LeafF l
        deriving (Show, Functor, Typeable)
    
    type instance Base (BiTree a b) = BiTreeF a b
    instance Recursive (BiTree a b) where
      project (Leaf x) = LeafF x
      project (Branch s l r) = BranchF s l r
    
    instance Corecursive (BiTree a b) where
      embed (BranchF sp x xs) = Branch sp x xs
      embed (LeafF x) = Leaf x
    

    您现在可以像正常一样在整个代码中使用您的基本类型(BiTree); 而当你决定使用递归方案时,你只需要记住在解包时使用'F'版本的构造函数:

    anyActiveWindows :: Window -> Bool
    anyActiveWindows = cata alg
      where alg (LeafF vw) = vw^.active
            alg (BranchF _ l r) = l || r
    

    请注意,如果最终重建一组窗口,则仍然会在=的右侧使用NON-F版本。

    我为我的场景定义了以下内容,效果很好; 我已经得到了FunctorBifunctor两个Window因为我甚至不使用newtype:

    type Window = BiTree Split View
    
    data SplitRule =
      Percentage Double
      | FromStart Int
      | FromEnd Int
      deriving (Show)
    
    data Dir = Hor
            | Vert
            deriving (Show)
    
    data Split = Split
      { _dir :: Dir
      , _splitRule :: SplitRule
      } deriving (Show)
    
    makeLenses ''Split
    
    data View = View
      { _active :: Bool
      , _bufIndex :: Int
      } deriving (Show)
    
    makeLenses ''View
    
    链接地址: http://www.djcxy.com/p/66633.html

    上一篇: type that's already a Functor?

    下一篇: Data families vs Injective type families