Skip to content

Commit

Permalink
More types, prettier output
Browse files Browse the repository at this point in the history
  • Loading branch information
jacobstanley committed Apr 21, 2019
1 parent 2bdf852 commit 451dc74
Show file tree
Hide file tree
Showing 7 changed files with 482 additions and 298 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)
1 change: 0 additions & 1 deletion hedgehog/hedgehog.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -132,7 +132,6 @@ test-suite test
other-modules:
Test.Hedgehog.Seed
Test.Hedgehog.Text
Test.Hedgehog.Classified

build-depends:
hedgehog
Expand Down
Loading

0 comments on commit 451dc74

Please sign in to comment.