1
1
mirror of https://github.com/github/semantic.git synced 2024-11-29 02:44:36 +03:00
semantic/test/Test/Hspec/LeanCheck.hs

96 lines
3.8 KiB
Haskell
Raw Normal View History

2017-01-08 07:16:27 +03:00
{-# LANGUAGE GADTs, TypeFamilies #-}
module Test.Hspec.LeanCheck
( prop
, forAll
2017-01-08 07:16:27 +03:00
) where
import Control.Exception
import Data.Bifunctor (first)
2017-07-28 21:37:02 +03:00
import Data.List (intercalate)
import Data.Maybe (listToMaybe)
import Data.Typeable
2017-01-08 07:16:27 +03:00
import GHC.Show as Show (showsPrec)
import Test.Hspec
2017-02-14 17:57:21 +03:00
import Test.Hspec.Core.Spec as Hspec
import qualified Test.HUnit.Lang as HUnit
2017-01-08 07:16:27 +03:00
import Test.LeanCheck.Core
data Property where
Property :: IOTestable prop => prop -> Property
-- | Perform an enumerative test of a property using LeanCheck.
--
-- 'prop' will typically be a function of one or more 'Listable' arguments, returning either 'Bool' or 'IO ()' (in the latter case, typically via 'shouldBe' and friends). For example:
--
-- > describe "+" $ do
-- > prop "associativity" $
-- > \ a b c -> a + (b + c) `shouldBe` (a + b :: Int) + c
2017-01-08 07:16:27 +03:00
prop :: (HasCallStack, IOTestable prop) => String -> prop -> Spec
prop s = it s . Property
data ForAll a where
ForAll :: IOTestable prop => [[a]] -> (a -> prop) -> ForAll a
-- | Test a property given by an explicit list of tiers rather than a 'Listable' instance. This can be used to e.g. filter input values for which the property does not hold.
--
-- > describe "mean" $ do
-- > prop "≥ the minimum" . forAll (not . null `filterT` tiers) $
-- > \ list -> (mean list :: Int) `shouldSatisfy` (>= min list)
forAll :: IOTestable prop => [[a]] -> (a -> prop) -> ForAll a
forAll = ForAll
2017-01-08 07:16:27 +03:00
instance Example Property where
type Arg Property = ()
evaluateExample (Property prop) (Params _ bound) _ _ = do
2017-02-14 17:57:21 +03:00
result <- try (iocounterExample bound prop)
2017-01-08 07:16:27 +03:00
case result of
2017-02-14 17:57:21 +03:00
Left e
| Just (LeanCheckException messages e') <- fromException e -> throw (addMessages messages e')
| otherwise -> throw e
2018-07-13 00:13:36 +03:00
Right (Just messages) -> pure $ Result "" (Failure Nothing (Reason (concat messages)))
Right Nothing -> pure $ Result "" Success
2017-02-14 17:57:21 +03:00
where addMessages messages (HUnit.HUnitFailure loc r) = HUnit.HUnitFailure loc $ case r of
2017-02-15 19:20:49 +03:00
HUnit.Reason s -> HUnit.Reason (intercalate "\n" messages ++ "\n" ++ s)
2017-02-14 17:57:21 +03:00
HUnit.ExpectedButGot Nothing expected actual -> HUnit.ExpectedButGot (Just (concat messages)) expected actual
HUnit.ExpectedButGot (Just preface) expected actual -> HUnit.ExpectedButGot (Just (intercalate "\n" messages ++ preface)) expected actual
2017-01-08 07:16:27 +03:00
class IOTestable t where
-- 'resultiers', lifted into 'IO'.
2017-01-12 23:51:01 +03:00
ioResultTiers :: t -> [[IO ([String], Bool)]]
2017-01-08 07:16:27 +03:00
instance IOTestable (IO ()) where
2017-02-14 17:57:21 +03:00
ioResultTiers action = [[ (action >> pure ([], True)) `catch` (throw . LeanCheckException []) ]]
2017-01-08 07:16:27 +03:00
instance (IOTestable b, Show a, Listable a) => IOTestable (a -> b) where
2017-02-14 17:57:21 +03:00
ioResultTiers p = concatMapT (resultiersFor p) tiers
2017-01-08 07:16:27 +03:00
instance IOTestable Bool where
2017-01-12 23:51:01 +03:00
ioResultTiers p = [[ pure ([], p) ]]
2017-01-08 07:16:27 +03:00
2017-02-14 17:57:21 +03:00
instance Show a => IOTestable (ForAll a) where
ioResultTiers (ForAll tiers property) = concatMapT (resultiersFor property) tiers
resultiersFor :: (IOTestable b, Show a) => (a -> b) -> a -> [[IO ([String], Bool)]]
resultiersFor p x = fmap (eval x) <$> ioResultTiers (p x)
2017-02-14 17:57:21 +03:00
eval :: Show a => a -> IO ([String], Bool) -> IO ([String], Bool)
eval x action = first (prepend x) <$> action
`catch` \ (LeanCheckException messages failure) -> throw (LeanCheckException (prepend x messages) failure)
where prepend x = (showsPrec 11 x "":)
2017-01-08 07:16:27 +03:00
-- | 'counterExamples', lifted into 'IO'.
2017-01-08 07:16:27 +03:00
iocounterExamples :: IOTestable a => Int -> a -> IO [[String]]
2017-01-12 23:51:01 +03:00
iocounterExamples n = fmap (fmap fst . filter (not . snd)) . sequenceA . take n . concat . ioResultTiers
2017-01-08 07:16:27 +03:00
-- | 'counterExample', lifted into 'IO'.
2017-01-08 07:16:27 +03:00
iocounterExample :: IOTestable a => Int -> a -> IO (Maybe [String])
iocounterExample n = fmap listToMaybe . iocounterExamples n
2017-02-14 17:57:21 +03:00
data LeanCheckException = LeanCheckException [String] HUnit.HUnitFailure
deriving (Show, Typeable)
instance Exception LeanCheckException