Haskell / SmallCheck: How to control the `Depth` parameter?

爷,独闯天下 提交于 2019-12-10 15:56:23

问题


I have a simple data structure to test in smallcheck.

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
{-# LANGUAGE DeriveGeneric #-}

import Test.Tasty
import Test.Tasty.SmallCheck
import Test.SmallCheck.Series
import GHC.Generics

data T1 = T1 { p1 :: Int,
               p2 :: Char,
               p3 :: [Int]
             } deriving (Eq, Show, Generic)

instance Monad m => Serial m T1

main :: IO ()
main = defaultMain tests

tests :: TestTree
tests = testGroup "Tests" [scProps]

scProps = testGroup "(checked by SmallCheck)"
  [ testProperty "Test1" prop_test1
  ]

prop_test1 x = x == x
             where types = (x :: T1)

When running the tests is there any general solution to set the Depth parameter for the (individual) tests, or better yet, a fine grained solution to set the Depth parameter for individual fields e.g. limit the depth of p3 to 2 to avoid the combinatorial explosion of the search space?

Many thanks in advance!

jules

info: A somewhat related question is here.

EDIT:
I took the solutions given in the accepted answer by Roman Cheplyaka and implemented them in a minimal working example (thanks, Roman):

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}

import Test.Tasty
import Test.Tasty.Options
import Test.Tasty.SmallCheck
import Test.SmallCheck.Series
import Data.Functor
-- =============================================================================
main :: IO ()
main = defaultMain tests
-- =============================================================================
-- the data structure to be tested
data T1 = T1 { p1 :: Int,
               p2 :: Char,
               p3 :: Int,
               p5 :: [Int]
             } deriving (Show, Eq)
-- =============================================================================
-- some test-properties
prop_test1 x y = x == y
               where types = (x :: T1, y :: T1)
prop_test2 x = x == x
             where types = (x :: T1)
-- =============================================================================
-- how to change the depth of the search spaces?
{-| I Possibility: Command Line |-}
-- foo@bar$ runhaskell Test.hs --smallcheck-depth 2

-- -----------------------------------------------------------------------------
{-| II Possibility: |-}
-- normal:
-- tests :: TestTree
-- tests = testGroup "Tests" [scProps]

-- custom:
tests :: TestTree
tests = localOption d $ testGroup "Tests" [scProps]
      where d = 3 :: SmallCheckDepth

scProps = testGroup "(checked by SmallCheck)"
  [ testProperty "Test1" prop_test1, 
    testProperty "Test2" prop_test2 
  ]

-- -----------------------------------------------------------------------------
{-| III Possibility: Adjust Depth when making the type instance of Serial |-}
-- normal:
-- instance (Monad m) => Serial m T1 where
--   series = T1 <$> series <~> series <~> series <~> series 

-- custom:
instance (Monad m) => Serial m T1 where
    series = localDepth (const 4) $ T1 <$> (localDepth (const 2) series) <~> series <~> series <~> (decDepth series) 

-- (a few more examples):
-- instance (Monad m) => Serial m T1 where
--    series = decDepth $ T1 <$> series <~> series <~> series <~> (decDepth series ) 
-- instance (Monad m) => Serial m T1 where
--   series = localDepth (const 3) $ T1 <$> series <~> series <~> series <~> series 
-- instance (Monad m) => Serial m T1 where
--    series = localDepth (const 4) $ T1 <$> series <~> series <~> series <~> (decDepth series) 

回答1:


I'll start by listing the means of control that tasty & smallcheck provide out of the box:

  • when running a test suite, you can pass the --smallcheck-depth option to control the «common» depth
  • when writing a test suite, you can use adjustOption to adjust the depth for any subtree relative to what has been specified on the command line (or for the parent trees)
  • finally, when writing Serial instances, you can use localDepth to adjust how much depth you want for each particular field, relative to the depth of the whole structure. Normally it's overall depth - 1 (that's what decDepth does in the standard definitions), but you can invent your own rules.

So, such control is possible, although in an indirect way. Typically it's what you want anyway — see also this answer.

If you really want to control depth of individual fields at runtime... yes, it's possible, although it's a bit complicated, because it wasn't an intended use case. (Still, it's pretty cool that it's possible at all!) Here's a working example.

If this functionality is important for you, maybe open an issue at github and explain why you need it. (But first, be sure to read my response to ocharles that is linked above. It's rare that you need to adjust the depth during runtime at all.)




回答2:


To summarize and exemplify, supposing you want to try with depth of two, you have several options.

When running the test suite (executable) directly:

./test --smallcheck-depth 2

When running a test suite from cabal:

cabal test --test-options="--smallcheck-depth 2"

By changing the depth in a testGroup/TestTree:

-- Global depth + 1  (usually supplied by command line)
props = adjustOption (+ SmallCheckDepth 1) $
        testGroup "some props"
          [ SC.testProperty myProp1
          , SC.testProperty myProp2
          ]

-- Local depth = 2
prps2 = localOption (SmallCheckDepth 2) $
        testGroup "fixed depth"
        [ ... ]

The adjustOption and localOption can also be used on specific properties. I personally think adjustOption is preferable, since it just tunes whatever is supplied by the command line or any enclosing TestTree.



来源:https://stackoverflow.com/questions/20582795/haskell-smallcheck-how-to-control-the-depth-parameter

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!