'Default Behavior' 对于 Haskell 递归数据类型

'Default Behavior' for Haskell recursive data types

我正在尝试在 Haskell 中编写一个命题逻辑求解器。我用称为 'Sentence' 的递归数据类型表示逻辑表达式,该数据类型具有用于不同操作的多个子类型 - 'AndSentence'、'OrSentence' 等。所以我猜它是一棵具有多种节点类型的树每个都有 0、1 或 2 children.

它似乎可以工作,但有些代码有点重复,我认为应该有更好的表达方式。基本上我有几个函数,其中 'default behavior' 只是让函数递归地作用于节点的 children,在某些节​​点类型(通常是 'AtomicSentences' 上触底) .所以我写了一个像这样的函数:

imply_remove :: Sentence Symbol -> Sentence Symbol
imply_remove (ImplySentence s1 s2) = OrSentence (NotSentence (imply_remove s1)) (imply_remove s2)
imply_remove (AndSentence s1 s2) = AndSentence (imply_remove s1) (imply_remove s2)
imply_remove (OrSentence s1 s2) = OrSentence (imply_remove s1) (imply_remove s2)
imply_remove (NotSentence s1) = NotSentence (imply_remove s1)
imply_remove (AtomicSentence s1) = AtomicSentence s1

我想要一种更简洁的方式来编写 'AndSentence'、'OrSentence' 和 'NotSentence' 的行。

看起来仿函数和我想要的很相似,但是没有成功...我想对子树进行操作,而不是对子树的每个节点中包含的某些值进行操作。

有正确的方法吗?或者更自然的方式来构建我的数据?

这看起来是 recursion-schemes 的一个不错的案例。

首先,我们将您的 Sentence sym 类型描述为类型级不动点 一个合适的仿函数。

{-# LANGUAGE DeriveFunctor, LambdaCase #-}

import Data.Functor.Foldable  -- from the recursion-schemes package

-- The functor describing the recursive data type
data SentenceF sym r
   = AtomicSentence sym
   | ImplySentence r r
   | AndSentence r r
   | OrSentence r r
   | NotSentence r
   deriving (Functor, Show)

-- The original type recovered via a fixed point
type Sentence sym = Fix (SentenceF sym)

上面的 Sentence sym 类型与您的原始类型几乎相同,只是所有内容都必须包含在 Fix 中。 调整原始代码以使用此类型是完全机械的: 我们以前使用 (Constructor ...),现在使用 Fix (Constructor ...)。例如

type Symbol = String

-- A simple formula: not (p -> (p || q))
testSentence :: Sentence Symbol
testSentence = 
   Fix $ NotSentence $
      Fix $ ImplySentence
         (Fix $ AtomicSentence "p")
         (Fix $ OrSentence
            (Fix $ AtomicSentence "p")
            (Fix $ AtomicSentence "q"))

这是您的原始代码,其中有冗余(额外的 Fixes 使情况变得更糟)。

-- The original code, adapted
imply_remove :: Sentence Symbol -> Sentence Symbol
imply_remove (Fix (ImplySentence s1 s2)) =
  Fix $ OrSentence (Fix $ NotSentence (imply_remove s1)) (imply_remove s2)
imply_remove (Fix (AndSentence s1 s2)) =
  Fix $ AndSentence (imply_remove s1) (imply_remove s2)
imply_remove (Fix (OrSentence s1 s2)) =
  Fix $ OrSentence (imply_remove s1) (imply_remove s2)
imply_remove (Fix (NotSentence s1)) =
  Fix $ NotSentence (imply_remove s1)
imply_remove (Fix (AtomicSentence s1)) =
  Fix $ AtomicSentence s1

让我们通过评估imply_remove testSentence来执行测试:结果是我们期望的:

 -- Output: not ((not p) || (p || q))
 Fix (NotSentence
   (Fix (OrSentence
      (Fix (NotSentence (Fix (AtomicSentence "p"))))
      (Fix (OrSentence
         (Fix (AtomicSentence "p"))
         (Fix (AtomicSentence "q")))))))

现在,让我们使用从递归计划中借来的核武器:

imply_remove2 :: Sentence Symbol -> Sentence Symbol
imply_remove2 = cata $ \case
   -- Rewrite ImplySentence as follows
   ImplySentence s1 s2 -> Fix $ OrSentence (Fix $ NotSentence s1) s2
   -- Keep everything else as it is (after it had been recursively processed)
   s -> Fix s

如果我们 运行 测试 imply_remove2 testSentence,我们得到与原始代码相同的输出。

cata 是做什么的?非常粗略地,当应用于像这样的函数时 在 cata f 中,它构建了一个 catamorphism,即一个函数

  1. 将公式分解成其子组件
  2. 递归地应用cata f到找到的子组件
  3. 将变换后的分量重新组装成公式
  4. 将最后一个公式(带有已处理的子公式)传递给 f,以便可以影响最顶层的连接词

最后一步才是真正的工作。上面的 \case 只执行了想要的转换。其他一切都由 cata 处理(以及自动生成的 Functor 实例)。

综上所述,我不建议任何人轻易搬到 recursion-schemes。使用 cata 可以产生非常优雅的代码,但它需要一个人了解所涉及的机制,这可能不是立即掌握的(这肯定不适合我)。

您要查找的内容在 Haskell 中称为 'generic programming':https://wiki.haskell.org/Generics; an early form was called "Scrap Your Boilerplate", which you also might want to Google. I haven't tested this, but I think if you use UniplateData.Generics.UniplateData.Generics.Uniplate.Data 模块您可以定义 imply_remove作为

imply_remove = transform w where
    w (ImplySentence s1 s2) = OrSentence (NotSentence s1) s2
    w s = s

transform 为您做递归。

您可以编写一个默认函数来定义在没有应用转换的情况下应如何处理符号:

default_transformation :: (Sentence Symbol -> Sentence Symbol) -> Sentence Symbol -> Sentence Symbol
default_transformation f (ImplySentence s1 s2) = ImplySentence (f s1) (f s2)
default_transformation f (AndSentence s1 s2) = AndSentence (f s1) (f s2)
default_transformation f (OrSentence s1 s2) = OrSentence (f s1) (f s2)
default_transformation f (NotSentence s1) = NotSentence (f s1)
default_transformation f (AtomicSentence s1) = AtomicSentence s1

该函数将特定转换作为参数。

如果您编写特定的转换,您只需编写与默认情况不同的情况,并将默认情况添加为最后一个情况:

imply_remove :: Sentence Symbol -> Sentence Symbol
imply_remove (ImplySentence s1 s2) = OrSentence (NotSentence (imply_remove s1)) (imply_remove s2)
imply_remove s = default_transformation imply_remove s

这种方法的优点是它可能更容易实现,因为它不需要任何依赖项。