具有相同函数名的多个函数定义

Multiple function definitions with same function name

在 Haskell 中如何解决(不使用函数而不是类型):

重写(真假)=假
重写(和(和真假)真)=假 ...

我尝试了以下

data MyLogic f a = And f a  deriving Show

rewrite(And a b)
 | a == False = False
 | b == False = False
 | otherwise = True

rewrite(And (And a b) c) = ...

但是 haskell 编译器抱怨说在第一次重写时 a 可能不是布尔值。

这个怎么样:

data MyLogic = Lit Bool
             | And MyLogic MyLogic deriving Show

rewrite :: Mylogic -> Bool
rewrite (Lit b) = b
rewrite (And a b) = rewrite a && rewrite b

我会像这样构建它

data MyLogic a = And (MyLogic a) a  deriving Show

rewrite :: (MyLogic Bool) -> Bool
rewrite (And f False) = False
rewrite (And f True) = rewrite f

具有相同名称的多个函数定义 只是临时多态性的另一个名称,这就是 Haskell 类型类的用途。

{-# LANGUAGE FlexibleInstances, FlexibleContexts #-}

data MyLogic f a = And f a  deriving Show

class Rewritable a where
   rewrite :: a -> Bool

instance Rewritable (MyLogic Bool Bool) where
  rewrite(And a b)
     | a == False = False
     | b == False = False
     | otherwise = True


instance Rewritable (MyLogic a b) => Rewritable  (MyLogic (MyLogic a b)  Bool) where
  rewrite(And x c) = rewrite $ And (rewrite x) c

这是 Hans Lub 方法的概括(实际上是完成),它应该适用于您正在考虑的任何类型的表达式。

{-# LANGUAGE FlexibleInstances, FlexibleContexts #-}
module MyLogic where

data MyLogic f a = And f a  deriving Show

class Rewritable a where
   rewrite :: a -> Bool

instance Rewritable Bool where
  rewrite = id

instance Rewritable (MyLogic Bool Bool) where
  rewrite(And a b) = a && b

instance Rewritable (MyLogic a b)
    => Rewritable  (MyLogic (MyLogic a b)  Bool) where
  rewrite(And x c) = rewrite $ And (rewrite x) c

instance Rewritable (MyLogic a b)
    => Rewritable  (MyLogic Bool (MyLogic a b)) where
  rewrite(And c x) = rewrite $ And c (rewrite x)

instance (Rewritable (MyLogic a b), Rewritable (MyLogic c d))
    => Rewritable (MyLogic (MyLogic a b) (MyLogic c d)) where
  rewrite(And x y) = rewrite $ And (rewrite x) (rewrite y)