使用HSpec和QuickCheck验证Data.Monoid属性 [英] Use HSpec and QuickCheck to verify Data.Monoid properties

查看:91
本文介绍了使用HSpec和QuickCheck验证Data.Monoid属性的处理方法,对大家解决问题具有一定的参考价值,需要的朋友们下面随着小编来一起学习吧!

问题描述

我正在尝试使用HSpec和QuickCheck来验证Monoid的属性(关联性和标识元素).我将验证特定的实例,但想保留大多数代码的多态性.这是几个小时后我想到的:

I'm trying to use HSpec and QuickCheck to verify properties of Monoids (associativity and identity element). I am going to verify particular instances, but would like to keep most of the code polymorphic. This is what I came up with after several hours:

module Test where

import Test.Hspec
import Test.QuickCheck
import Data.Monoid

instance (Arbitrary a) => Arbitrary (Sum a) where
    arbitrary = fmap Sum arbitrary

instance (Arbitrary a) => Arbitrary (Product a) where
    arbitrary = fmap Product arbitrary

prop_Monoid_mappend_mempty_x x = mappend mempty x === x

sumMonoidSpec = it "mappend mempty x = x" $ property (prop_Monoid_mappend_mempty_x :: Sum Int -> Property)
productMonoidSpec = it "mappend mempty x = x" $ property (prop_Monoid_mappend_mempty_x :: Product Double -> Property)

main :: IO ()
main = hspec $ do
    describe "Data.Monoid.Sum" $ do
        sumMonoidSpec
    describe "Data.Monoid.Product" $ do
        productMonoidSpec

我想拥有的是多态的

monoidSpec = it "mappend mempty x = x" $ property prop_Monoid_mappend_mempty_x

,然后指定实际的Monoid实例(Sum,Product)和类型(Int,Double).问题是它不会进行类型检查.我不断得到

and specify the actual Monoid instance (Sum, Product) and the type (Int, Double) later on. The issue is it wouldn't type check. I keep getting

src/Test.hs@18:42-18:50 No instance for (Arbitrary a0) arising from a use of property
The type variable a0 is ambiguous
Note: there are several potential instances:
  instance Arbitrary a => Arbitrary (Product a)
    -- Defined at /home/app/isolation-runner-work/projects/68426/session.207/src/src/Test.hs:10:10
  instance Arbitrary a => Arbitrary (Sum a)
    -- Defined at /home/app/isolation-runner-work/projects/68426/session.207/src/src/Test.hs:7:10
  instance Arbitrary () -- Defined in Test.QuickCheck.Arbitrary
  ...plus 27 others …
src/Test.hs@18:51-18:79 No instance for (Monoid a0)
  arising from a use of prop_Monoid_mappend_mempty_x
The type variable a0 is ambiguous
Note: there are several potential instances:
  instance Monoid () -- Defined in Data.Monoid
  instance (Monoid a, Monoid b) => Monoid (a, b)
    -- Defined in Data.Monoid
  instance (Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)
    -- Defined in Data.Monoid
  ...plus 18 others …

我知道我需要在多态版本中将Monoid约束为任意,均衡和显示,但我不知道如何.

I know I need to constraint Monoid in polymorphic version to be Arbitrary, Eq and Show but I don't know how.

问题是如何以多态方式表达Monoid的规范并避免代码重复?

The question is how to express specs for Monoid in a polymorphic way and avoid code duplication?

推荐答案

注意property :: Testable prop => prop -> Property的类型.类型var prop被删除,并且如果类型变量不再可用,则实例解析无法进行.基本上,您要做的是将instace选择推迟,并且必须在选择实例之前使该类型可用.

Notice the type of property :: Testable prop => prop -> Property. The type var prop is erased, and instance resolution can't take place if the type variable is no longer available. Basically what you want to do is defer instace selection, and to do that you must make the type available until the moment you pick the instance.

一种方法是携带一个额外的Proxy prop参数:

One way is to carry around an extra Proxy prop parameter:

-- Possibly Uuseful helper function
propertyP :: Testable prop => Proxy prop -> prop -> Property 
propertyP _ = property 

monoidProp :: forall m . (Arbitrary m, Testable m, Show m, Monoid m, Eq m) 
           => Proxy m -> Property 
monoidProp _ = property (prop_Monoid_mappend_mempty_x :: m -> Property)

monoidSpec :: (Monoid m, Arbitrary m, Testable m, Show m, Eq m) => Proxy m -> Spec
monoidSpec x = it "mappend mempty x = x" $ monoidProp x 

main0 :: IO ()
main0 = hspec $ do
    describe "Data.Monoid.Sum" $ do
        monoidSpec (Proxy :: Proxy (Sum Int))
    describe "Data.Monoid.Product" $ do
        monoidSpec (Proxy :: Proxy (Product Double))

另一种方法是使用像tagged这样的库,该库提供类型Tagged,该库仅向现有类型添加一些幻像类型参数:

Another way is to use a library like tagged which provides the type Tagged, which simply adds some phantom type parameter to an existing type:

import Data.Tagged

type TaggedProp a = Tagged a Property 
type TaggedSpec a = Tagged a Spec 

monoidPropT :: forall a. (Monoid a, Arbitrary a, Show a, Eq a) 
            => TaggedProp a
monoidPropT = Tagged (property (prop_Monoid_mappend_mempty_x :: a -> Property))

monoidSpecT :: forall a . (Monoid a, Arbitrary a, Show a, Eq a) => TaggedSpec a
monoidSpecT = Tagged $ it "mappend mempty x = x" 
                          (unTagged (monoidPropT :: TaggedProp a))

main1 :: IO ()
main1 = hspec $ do
    describe "Data.Monoid.Sum" $ do
        untag (monoidSpecT :: TaggedSpec (Sum Int))
    describe "Data.Monoid.Product" $ do
        untag (monoidSpecT :: TaggedSpec (Product Double))

这些解决方案在本质上是等效的,尽管在某些情况下,一种或另一种可能更方便.由于我对您的用例了解不足,因此将两者都包括在内.

These solutions are essentially equivalent, although in some cases one or the other may be much more convenient. Since I don't know enough about your use case, I've included both.

这两个都只需要-XScopedTypeVariables.

这篇关于使用HSpec和QuickCheck验证Data.Monoid属性的文章就介绍到这了,希望我们推荐的答案对大家有所帮助,也希望大家多多支持IT屋!

查看全文
登录 关闭
扫码关注1秒登录
发送“验证码”获取 | 15天全站免登陆