hspec-leancheck-0.0.3: LeanCheck support for the Hspec test framework.

Copyright(c) 2018 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellNone
LanguageHaskell2010

Test.Hspec.LeanCheck

Contents

Description

LeanCheck support for the Hspec test framework.

Here's how your spec.hs might look like:

import Test.Hspec
import Test.Hspec.LeanCheck as LC

import Data.List (sort)

main :: IO ()
main = hspec spec

spec :: Spec
spec = do
  describe "sort" $ do
    it "is idempotent" $
      LC.property $ \xs -> sort (sort xs :: [Int]) == sort xs
    it "is identity" $ -- not really
      LC.property $ \xs -> sort (xs :: [Int]) == xs

The output for the above program is:

$ ./eg/minimal

sort
  is idempotent
  is identity FAILED [1]

Failures:

  eg/minimal.hs:17:5:
  1) sort is identity
       [1,0]

  To rerun use: --match "/sort/is identity/"

2 examples, 1 failure

Please see the documentation of Test.LeanCheck and Hspec for more details.

Synopsis

Documentation

property :: Testable a => a -> Property Source #

Allows a LeanCheck Testable property to appear in a Spec. Like so:

spec :: Spec
spec = do
  describe "thing" $ do
   it "is so and so" $ property $ \x... -> ...
   it "is like this" $ property $ \y... -> ...
   ...

propertyFor :: Testable a => Int -> a -> Property Source #

Like property but allows setting the maximum number of tests.

spec :: Spec
spec = do
  describe "thing" $ do
   it "is so and so" $ propertyFor 100 $ \... -> ...
   it "is like this" $ propertyFor 200 $ \... -> ...
   it "does a thing" $ propertyFor 300 $ \... -> ...
   ...

prop :: Testable a => String -> a -> Spec Source #

Allows a named LeanCheck Testable property to appear in a Spec.

prop "does so and so" $ ...

is a shortcut for

it "does so an so" $ property $ ...
spec :: Spec
spec = do
  describe "thing" $ do
   prop "is so and so" $ \x... -> ...
   prop "is like this" $ \y... -> ...
   ...

data Property Source #

A LeanCheck property. See property, propertyFor and prop.

Instances
Example Property Source # 
Instance details

Defined in Test.Hspec.LeanCheck

Associated Types

type Arg Property :: *

Methods

evaluateExample :: Property -> Params -> (ActionWith (Arg Property) -> IO ()) -> ProgressCallback -> IO Result

type Arg Property Source # 
Instance details

Defined in Test.Hspec.LeanCheck

type Arg Property = ()

Orphan instances

Testable (IO a) Source #

Allows should* to appear inside LeanCheck properties

Example:

describe "sort" $ do
  it "is idempotent" $
    LC.property $ \xs -> sort (sort xs :: [Int]) `shouldBe` sort xs
Instance details

Methods

resultiers :: IO a -> [[([String], Bool)]] #