二叉树的应用同态律



我知道存在以下问题:

haskell -如何快速检查应用同态属性?- Stack Overflow

但是,下面的PRAGMA

的引入
{-# LANGUAGE ScopedTypeVariables #-}

没有解决我的问题。

以下是我的定义:

{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Laws where
import Control.Applicative ((<$>), liftA3)
import Data.Monoid
import Test.QuickCheck
import Test.QuickCheck.Function
import Test.QuickCheck.Gen
data BinTree a = Empty | Node a (BinTree a) (BinTree a) deriving (Show, Eq)
instance Functor BinTree where
fmap _ Empty = Empty
fmap f (Node x hi hd) = Node (f x) (fmap f hi) (fmap f hd)
instance Applicative BinTree where
-- pure :: a -> BinTree a
pure x = Node x (pure x) (pure x)
-- <*> :: BinTree (a -> b) -> BinTree a -> BinTree b
_ <*> Empty = Empty -- L1, 
Empty <*> t = Empty
(Node f l r) <*> (Node x l' r') = Node (f x) (l <*> l') (r <*> r')
instance (Arbitrary a) => Arbitrary (BinTree a) where
arbitrary = oneof [return Empty, -- oneof :: [Gen a] -> Gen a
liftA3 Node arbitrary arbitrary arbitrary]

-- Identity
apIdentityProp :: (Applicative f, Eq (f a)) => f a -> Bool
apIdentityProp v = (pure id <*> v) == v
-- pure f <*> pure x = pure (f x)   -- Homomorphism
apHomomorphismProp :: forall f a b. (Applicative f, Eq (f b)) => Fun a b -> a -> Bool
apHomomorphismProp (apply -> g) x = (((pure g :: f (a -> b)) <*> (pure x :: f a)) :: f b) == (pure (g x) :: f b)
main :: IO ()
main = quickCheck (apHomomorphismProp :: Fun Int Int -> Int -> Bool)

如何修复以下错误?

无法推断(Applicative f0)(Applicative f, Eq (f b))

如果包含完整的错误消息(其中提到了一个不明确的类型变量),那么分析问题就会更容易。GHC抱怨的是,fapHomomorphismProp的类型签名中,除了量词和约束外,没有出现在任何地方。

为什么这是个问题?嗯,这不是问题……但它曾经是在旧的Haskell版本,因为没有办法让编译器告诉当你使用apHomomorphismProp它应该在这里测试什么应用程序。事实上,这仍然是您使用它的方式的情况:apHomomorphismProp :: Fun Int Int -> Int -> Bool没有以任何方式提到BinTree,那么编译器应该如何知道这就是你的意思?对于它所知道的一切,您也可以要求,例如,在这里测试Maybe应用程序。

解决方案,在现代Haskell中,是-XTypeApplications,它只是让你显式地说明应该用什么类型变量实例化。

{-# LANGUAGE TypeApplications #-}
main = quickCheck (apHomomorphismProp @BinTree :: Fun Int Int -> Int -> Bool)

事实上,我也建议使用这种语法来澄清Int类型:

main = quickCheck $ apHomomorphismProp @BinTree @Int @Int

然而,apHomomorphismProp仍然存在编译错误,这都是因为在TypeApplications之前,您给apHomomorphismProp的签名是无用的。但是这个限制现在已经过时了,可以通过-XAllowAmbiguousTypes:

禁用它。
{-# LANGUAGE ScopedTypeVariables, UnicodeSyntax, AllowAmbiguousTypes, TypeApplications #-}
apHomomorphismProp :: ∀ f a b. (Applicative f, Eq (f b)) => Fun a b -> a -> Bool
apHomomorphismProp (apply -> g) x = (pure @f g <*> pure x) == pure (g x)

请注意,我只需要为其中一个pures提到@f,其他的会自动约束到相同的应用程序。


它是否真的过时是有争议的。可能仍然正确的是,如果初学者给他们的函数一个模棱两可的类型,它更有可能是一个错误,应该当场抓住,而不是实际打算用-XTypeApplications。一个无意中产生歧义的类型会导致相当混乱的错误。

最新更新