Skip to content

Commit

Permalink
Merge pull request #253 from felixmulder/topic/add-classifications
Browse files Browse the repository at this point in the history
Add classifications to properties
  • Loading branch information
jacobstanley authored Apr 21, 2019
2 parents 143995b + d44f72a commit ada4caa
Show file tree
Hide file tree
Showing 5 changed files with 498 additions and 107 deletions.
40 changes: 40 additions & 0 deletions hedgehog-example/src/Test/Example/Coverage.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,40 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Test.Example.Coverage (
tests
) where

import Control.Concurrent (threadDelay)

import Data.Foldable (for_)

import Hedgehog
import qualified Hedgehog.Gen as Gen
import qualified Hedgehog.Range as Range

prop_classify :: Property
prop_classify =
withTests 1 . property $ do
for_ [1 :: Int ..100] $ \a -> do
classify "small number" $ a < 50
classify "big number" $ a >= 50

prop_cover_number :: Property
prop_cover_number =
property $ do
number <- forAll (Gen.int $ Range.linear 1 100)
evalIO $ threadDelay 20000
cover 50 "small number" $ number < 50
cover 50 "medium number" $ number >= 20
cover 50 "big number" $ number >= 50

prop_cover_bool :: Property
prop_cover_bool =
property $ do
match <- forAll Gen.bool
cover 30 "True" match
cover 30 "False" $ not match

tests :: IO Bool
tests =
checkParallel $$(discover)
7 changes: 5 additions & 2 deletions hedgehog/src/Hedgehog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,8 @@ module Hedgehog (

, forAll
, forAllWith
, classify
, cover
, discard

, check
Expand Down Expand Up @@ -151,8 +153,9 @@ import Hedgehog.Internal.Distributive (Distributive(..))
import Hedgehog.Internal.Gen (Gen, GenT, MonadGen(..))
import Hedgehog.Internal.HTraversable (HTraversable(..))
import Hedgehog.Internal.Opaque (Opaque(..))
import Hedgehog.Internal.Property (assert, diff, annotate, annotateShow)
import Hedgehog.Internal.Property ((===), (/==))
import Hedgehog.Internal.Property (annotate, annotateShow)
import Hedgehog.Internal.Property (assert, diff, (===), (/==))
import Hedgehog.Internal.Property (classify, cover)
import Hedgehog.Internal.Property (discard, failure, success)
import Hedgehog.Internal.Property (DiscardLimit, withDiscards)
import Hedgehog.Internal.Property (eval, evalM, evalIO)
Expand Down
Loading

0 comments on commit ada4caa

Please sign in to comment.