{-# OPTIONS_HADDOCK not-home #-}
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DoAndIfThenElse #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-} -- Distributive

module Hedgehog.Internal.Property (
  -- * Property
    Property(..)
  , PropertyT(..)
  , PropertyName(..)
  , PropertyConfig(..)
  , TestLimit(..)
  , TestCount(..)
  , DiscardLimit(..)
  , DiscardCount(..)
  , ShrinkLimit(..)
  , ShrinkCount(..)
  , ShrinkRetries(..)
  , withTests
  , withDiscards
  , withShrinks
  , withRetries
  , property
  , test
  , forAll
  , forAllT
  , forAllWith
  , forAllWithT
  , defaultMinTests
  , discard

  -- * Group
  , Group(..)
  , GroupName(..)
  , PropertyCount(..)

  -- * TestT
  , MonadTest(..)
  , Test
  , TestT(..)
  , Log(..)
  , Journal(..)
  , Failure(..)
  , Diff(..)
  , annotate
  , annotateShow
  , footnote
  , footnoteShow
  , failure
  , success
  , assert
  , diff
  , (===)
  , (/==)

  , eval
  , evalNF
  , evalM
  , evalIO
  , evalEither
  , evalEitherM
  , evalExceptT
  , evalMaybe
  , evalMaybeM

  -- * Coverage
  , Coverage(..)
  , Label(..)
  , LabelName(..)
  , cover
  , classify
  , label
  , collect
  , coverPercentage
  , labelCovered
  , coverageSuccess
  , coverageFailures
  , journalCoverage

  , Cover(..)
  , CoverCount(..)
  , CoverPercentage(..)
  , toCoverCount

  -- * Confidence
  , Confidence(..)
  , TerminationCriteria(..)
  , confidenceSuccess
  , confidenceFailure
  , withConfidence
  , verifiedTermination
  , defaultConfidence

  -- * Internal
  -- $internal
  , defaultConfig
  , mapConfig
  , failDiff
  , failException
  , failWith
  , writeLog

  , mkTest
  , mkTestT
  , runTest
  , runTestT

  , wilsonBounds
  ) where

import           Control.Applicative (Alternative(..))
import           Control.DeepSeq (NFData, rnf)
import           Control.Monad (MonadPlus(..), (<=<))
import           Control.Monad.Base (MonadBase(..))
import           Control.Monad.Catch (MonadThrow(..), MonadCatch(..))
import           Control.Monad.Catch (SomeException(..), displayException)
import           Control.Monad.Error.Class (MonadError(..))
import qualified Control.Monad.Fail as Fail
import           Control.Monad.IO.Class (MonadIO(..))
import           Control.Monad.Morph (MFunctor(..))
import           Control.Monad.Primitive (PrimMonad(..))
import           Control.Monad.Reader.Class (MonadReader(..))
import           Control.Monad.State.Class (MonadState(..))
import           Control.Monad.Trans.Class (MonadTrans(..))
import           Control.Monad.Trans.Cont (ContT)
import           Control.Monad.Trans.Control (ComposeSt, defaultLiftBaseWith, defaultRestoreM)
import           Control.Monad.Trans.Control (MonadBaseControl(..), MonadTransControl(..))
import           Control.Monad.Trans.Except (ExceptT(..), runExceptT)
import           Control.Monad.Trans.Identity (IdentityT)
import           Control.Monad.Trans.Maybe (MaybeT)
import qualified Control.Monad.Trans.RWS.Lazy as Lazy
import qualified Control.Monad.Trans.RWS.Strict as Strict
import           Control.Monad.Trans.Reader (ReaderT)
import           Control.Monad.Trans.Resource (MonadResource(..))
import           Control.Monad.Trans.Resource (ResourceT)
import qualified Control.Monad.Trans.State.Lazy as Lazy
import qualified Control.Monad.Trans.State.Strict as Strict
import qualified Control.Monad.Trans.Writer.Lazy as Lazy
import qualified Control.Monad.Trans.Writer.Strict as Strict

import qualified Data.Char as Char
import           Data.Functor (($>))
import           Data.Functor.Identity (Identity(..))
import           Data.Int (Int64)
import           Data.Map (Map)
import qualified Data.Map.Strict as Map
import           Data.Number.Erf (invnormcdf)
import qualified Data.List as List
import           Data.String (IsString)
import           Data.Ratio ((%))
import           Data.Typeable (typeOf)

import           Hedgehog.Internal.Distributive
import           Hedgehog.Internal.Exception
import           Hedgehog.Internal.Gen (Gen, GenT)
import qualified Hedgehog.Internal.Gen as Gen
import           Hedgehog.Internal.Prelude
import           Hedgehog.Internal.Show
import           Hedgehog.Internal.Source

import           Language.Haskell.TH.Syntax (Lift)


------------------------------------------------------------------------

-- | A property test, along with some configurable limits like how many times
--   to run the test.
--
data Property =
  Property {
      Property -> PropertyConfig
propertyConfig :: !PropertyConfig
    , Property -> PropertyT IO ()
propertyTest :: PropertyT IO ()
    }

-- | The property monad transformer allows both the generation of test inputs
--   and the assertion of expectations.
--
newtype PropertyT m a =
  PropertyT {
      PropertyT m a -> TestT (GenT m) a
unPropertyT :: TestT (GenT m) a
    } deriving (
      a -> PropertyT m b -> PropertyT m a
(a -> b) -> PropertyT m a -> PropertyT m b
(forall a b. (a -> b) -> PropertyT m a -> PropertyT m b)
-> (forall a b. a -> PropertyT m b -> PropertyT m a)
-> Functor (PropertyT m)
forall a b. a -> PropertyT m b -> PropertyT m a
forall a b. (a -> b) -> PropertyT m a -> PropertyT m b
forall (m :: * -> *) a b.
Functor m =>
a -> PropertyT m b -> PropertyT m a
forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> PropertyT m a -> PropertyT m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> PropertyT m b -> PropertyT m a
$c<$ :: forall (m :: * -> *) a b.
Functor m =>
a -> PropertyT m b -> PropertyT m a
fmap :: (a -> b) -> PropertyT m a -> PropertyT m b
$cfmap :: forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> PropertyT m a -> PropertyT m b
Functor
    , Functor (PropertyT m)
a -> PropertyT m a
Functor (PropertyT m)
-> (forall a. a -> PropertyT m a)
-> (forall a b.
    PropertyT m (a -> b) -> PropertyT m a -> PropertyT m b)
-> (forall a b c.
    (a -> b -> c) -> PropertyT m a -> PropertyT m b -> PropertyT m c)
-> (forall a b. PropertyT m a -> PropertyT m b -> PropertyT m b)
-> (forall a b. PropertyT m a -> PropertyT m b -> PropertyT m a)
-> Applicative (PropertyT m)
PropertyT m a -> PropertyT m b -> PropertyT m b
PropertyT m a -> PropertyT m b -> PropertyT m a
PropertyT m (a -> b) -> PropertyT m a -> PropertyT m b
(a -> b -> c) -> PropertyT m a -> PropertyT m b -> PropertyT m c
forall a. a -> PropertyT m a
forall a b. PropertyT m a -> PropertyT m b -> PropertyT m a
forall a b. PropertyT m a -> PropertyT m b -> PropertyT m b
forall a b. PropertyT m (a -> b) -> PropertyT m a -> PropertyT m b
forall a b c.
(a -> b -> c) -> PropertyT m a -> PropertyT m b -> PropertyT m c
forall (m :: * -> *). Monad m => Functor (PropertyT m)
forall (m :: * -> *) a. Monad m => a -> PropertyT m a
forall (m :: * -> *) a b.
Monad m =>
PropertyT m a -> PropertyT m b -> PropertyT m a
forall (m :: * -> *) a b.
Monad m =>
PropertyT m a -> PropertyT m b -> PropertyT m b
forall (m :: * -> *) a b.
Monad m =>
PropertyT m (a -> b) -> PropertyT m a -> PropertyT m b
forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> PropertyT m a -> PropertyT m b -> PropertyT m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: PropertyT m a -> PropertyT m b -> PropertyT m a
$c<* :: forall (m :: * -> *) a b.
Monad m =>
PropertyT m a -> PropertyT m b -> PropertyT m a
*> :: PropertyT m a -> PropertyT m b -> PropertyT m b
$c*> :: forall (m :: * -> *) a b.
Monad m =>
PropertyT m a -> PropertyT m b -> PropertyT m b
liftA2 :: (a -> b -> c) -> PropertyT m a -> PropertyT m b -> PropertyT m c
$cliftA2 :: forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> PropertyT m a -> PropertyT m b -> PropertyT m c
<*> :: PropertyT m (a -> b) -> PropertyT m a -> PropertyT m b
$c<*> :: forall (m :: * -> *) a b.
Monad m =>
PropertyT m (a -> b) -> PropertyT m a -> PropertyT m b
pure :: a -> PropertyT m a
$cpure :: forall (m :: * -> *) a. Monad m => a -> PropertyT m a
$cp1Applicative :: forall (m :: * -> *). Monad m => Functor (PropertyT m)
Applicative
    , Applicative (PropertyT m)
a -> PropertyT m a
Applicative (PropertyT m)
-> (forall a b.
    PropertyT m a -> (a -> PropertyT m b) -> PropertyT m b)
-> (forall a b. PropertyT m a -> PropertyT m b -> PropertyT m b)
-> (forall a. a -> PropertyT m a)
-> Monad (PropertyT m)
PropertyT m a -> (a -> PropertyT m b) -> PropertyT m b
PropertyT m a -> PropertyT m b -> PropertyT m b
forall a. a -> PropertyT m a
forall a b. PropertyT m a -> PropertyT m b -> PropertyT m b
forall a b. PropertyT m a -> (a -> PropertyT m b) -> PropertyT m b
forall (m :: * -> *). Monad m => Applicative (PropertyT m)
forall (m :: * -> *) a. Monad m => a -> PropertyT m a
forall (m :: * -> *) a b.
Monad m =>
PropertyT m a -> PropertyT m b -> PropertyT m b
forall (m :: * -> *) a b.
Monad m =>
PropertyT m a -> (a -> PropertyT m b) -> PropertyT m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> PropertyT m a
$creturn :: forall (m :: * -> *) a. Monad m => a -> PropertyT m a
>> :: PropertyT m a -> PropertyT m b -> PropertyT m b
$c>> :: forall (m :: * -> *) a b.
Monad m =>
PropertyT m a -> PropertyT m b -> PropertyT m b
>>= :: PropertyT m a -> (a -> PropertyT m b) -> PropertyT m b
$c>>= :: forall (m :: * -> *) a b.
Monad m =>
PropertyT m a -> (a -> PropertyT m b) -> PropertyT m b
$cp1Monad :: forall (m :: * -> *). Monad m => Applicative (PropertyT m)
Monad
    , Monad (PropertyT m)
Monad (PropertyT m)
-> (forall a. IO a -> PropertyT m a) -> MonadIO (PropertyT m)
IO a -> PropertyT m a
forall a. IO a -> PropertyT m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
forall (m :: * -> *). MonadIO m => Monad (PropertyT m)
forall (m :: * -> *) a. MonadIO m => IO a -> PropertyT m a
liftIO :: IO a -> PropertyT m a
$cliftIO :: forall (m :: * -> *) a. MonadIO m => IO a -> PropertyT m a
$cp1MonadIO :: forall (m :: * -> *). MonadIO m => Monad (PropertyT m)
MonadIO
    , MonadBase b
    , Monad (PropertyT m)
e -> PropertyT m a
Monad (PropertyT m)
-> (forall e a. Exception e => e -> PropertyT m a)
-> MonadThrow (PropertyT m)
forall e a. Exception e => e -> PropertyT m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
forall (m :: * -> *). MonadThrow m => Monad (PropertyT m)
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> PropertyT m a
throwM :: e -> PropertyT m a
$cthrowM :: forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> PropertyT m a
$cp1MonadThrow :: forall (m :: * -> *). MonadThrow m => Monad (PropertyT m)
MonadThrow
    , MonadThrow (PropertyT m)
MonadThrow (PropertyT m)
-> (forall e a.
    Exception e =>
    PropertyT m a -> (e -> PropertyT m a) -> PropertyT m a)
-> MonadCatch (PropertyT m)
PropertyT m a -> (e -> PropertyT m a) -> PropertyT m a
forall e a.
Exception e =>
PropertyT m a -> (e -> PropertyT m a) -> PropertyT m a
forall (m :: * -> *). MonadCatch m => MonadThrow (PropertyT m)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
PropertyT m a -> (e -> PropertyT m a) -> PropertyT m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
catch :: PropertyT m a -> (e -> PropertyT m a) -> PropertyT m a
$ccatch :: forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
PropertyT m a -> (e -> PropertyT m a) -> PropertyT m a
$cp1MonadCatch :: forall (m :: * -> *). MonadCatch m => MonadThrow (PropertyT m)
MonadCatch
    , MonadReader r
    , MonadState s
    , MonadError e
    )
-- NOTE: Move this to the deriving list above when we drop 7.10
deriving instance MonadResource m => MonadResource (PropertyT m)

-- NOTE: Move this to the deriving list above when we drop 8.0
#if __GLASGOW_HASKELL__ >= 802
deriving instance MonadBaseControl b m => MonadBaseControl b (PropertyT m)
#else
instance MonadBaseControl b m => MonadBaseControl b (PropertyT m) where
  type StM (PropertyT m) a = StM (TestT (GenT m)) a
  liftBaseWith f = PropertyT $ liftBaseWith $ \rib -> f (rib . unPropertyT)
  restoreM = PropertyT . restoreM
#endif

-- | A test monad allows the assertion of expectations.
--
type Test =
  TestT Identity

-- | A test monad transformer allows the assertion of expectations.
--
newtype TestT m a =
  TestT {
      TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest :: ExceptT Failure (Lazy.WriterT Journal m) a
    } deriving (
      a -> TestT m b -> TestT m a
(a -> b) -> TestT m a -> TestT m b
(forall a b. (a -> b) -> TestT m a -> TestT m b)
-> (forall a b. a -> TestT m b -> TestT m a) -> Functor (TestT m)
forall a b. a -> TestT m b -> TestT m a
forall a b. (a -> b) -> TestT m a -> TestT m b
forall (m :: * -> *) a b. Functor m => a -> TestT m b -> TestT m a
forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> TestT m a -> TestT m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> TestT m b -> TestT m a
$c<$ :: forall (m :: * -> *) a b. Functor m => a -> TestT m b -> TestT m a
fmap :: (a -> b) -> TestT m a -> TestT m b
$cfmap :: forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> TestT m a -> TestT m b
Functor
    , Functor (TestT m)
a -> TestT m a
Functor (TestT m)
-> (forall a. a -> TestT m a)
-> (forall a b. TestT m (a -> b) -> TestT m a -> TestT m b)
-> (forall a b c.
    (a -> b -> c) -> TestT m a -> TestT m b -> TestT m c)
-> (forall a b. TestT m a -> TestT m b -> TestT m b)
-> (forall a b. TestT m a -> TestT m b -> TestT m a)
-> Applicative (TestT m)
TestT m a -> TestT m b -> TestT m b
TestT m a -> TestT m b -> TestT m a
TestT m (a -> b) -> TestT m a -> TestT m b
(a -> b -> c) -> TestT m a -> TestT m b -> TestT m c
forall a. a -> TestT m a
forall a b. TestT m a -> TestT m b -> TestT m a
forall a b. TestT m a -> TestT m b -> TestT m b
forall a b. TestT m (a -> b) -> TestT m a -> TestT m b
forall a b c. (a -> b -> c) -> TestT m a -> TestT m b -> TestT m c
forall (m :: * -> *). Monad m => Functor (TestT m)
forall (m :: * -> *) a. Monad m => a -> TestT m a
forall (m :: * -> *) a b.
Monad m =>
TestT m a -> TestT m b -> TestT m a
forall (m :: * -> *) a b.
Monad m =>
TestT m a -> TestT m b -> TestT m b
forall (m :: * -> *) a b.
Monad m =>
TestT m (a -> b) -> TestT m a -> TestT m b
forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> TestT m a -> TestT m b -> TestT m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: TestT m a -> TestT m b -> TestT m a
$c<* :: forall (m :: * -> *) a b.
Monad m =>
TestT m a -> TestT m b -> TestT m a
*> :: TestT m a -> TestT m b -> TestT m b
$c*> :: forall (m :: * -> *) a b.
Monad m =>
TestT m a -> TestT m b -> TestT m b
liftA2 :: (a -> b -> c) -> TestT m a -> TestT m b -> TestT m c
$cliftA2 :: forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> TestT m a -> TestT m b -> TestT m c
<*> :: TestT m (a -> b) -> TestT m a -> TestT m b
$c<*> :: forall (m :: * -> *) a b.
Monad m =>
TestT m (a -> b) -> TestT m a -> TestT m b
pure :: a -> TestT m a
$cpure :: forall (m :: * -> *) a. Monad m => a -> TestT m a
$cp1Applicative :: forall (m :: * -> *). Monad m => Functor (TestT m)
Applicative
    , Monad (TestT m)
Monad (TestT m)
-> (forall a. IO a -> TestT m a) -> MonadIO (TestT m)
IO a -> TestT m a
forall a. IO a -> TestT m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
forall (m :: * -> *). MonadIO m => Monad (TestT m)
forall (m :: * -> *) a. MonadIO m => IO a -> TestT m a
liftIO :: IO a -> TestT m a
$cliftIO :: forall (m :: * -> *) a. MonadIO m => IO a -> TestT m a
$cp1MonadIO :: forall (m :: * -> *). MonadIO m => Monad (TestT m)
MonadIO
    , MonadBase b
    , Monad (TestT m)
e -> TestT m a
Monad (TestT m)
-> (forall e a. Exception e => e -> TestT m a)
-> MonadThrow (TestT m)
forall e a. Exception e => e -> TestT m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
forall (m :: * -> *). MonadThrow m => Monad (TestT m)
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> TestT m a
throwM :: e -> TestT m a
$cthrowM :: forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> TestT m a
$cp1MonadThrow :: forall (m :: * -> *). MonadThrow m => Monad (TestT m)
MonadThrow
    , MonadThrow (TestT m)
MonadThrow (TestT m)
-> (forall e a.
    Exception e =>
    TestT m a -> (e -> TestT m a) -> TestT m a)
-> MonadCatch (TestT m)
TestT m a -> (e -> TestT m a) -> TestT m a
forall e a.
Exception e =>
TestT m a -> (e -> TestT m a) -> TestT m a
forall (m :: * -> *). MonadCatch m => MonadThrow (TestT m)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
TestT m a -> (e -> TestT m a) -> TestT m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
catch :: TestT m a -> (e -> TestT m a) -> TestT m a
$ccatch :: forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
TestT m a -> (e -> TestT m a) -> TestT m a
$cp1MonadCatch :: forall (m :: * -> *). MonadCatch m => MonadThrow (TestT m)
MonadCatch
    , MonadReader r
    , MonadState s
    )

-- | The name of a property.
--
--   Should be constructed using `OverloadedStrings`:
--
-- @
--   "apples" :: PropertyName
-- @
--
newtype PropertyName =
  PropertyName {
      PropertyName -> String
unPropertyName :: String
    } deriving (PropertyName -> PropertyName -> Bool
(PropertyName -> PropertyName -> Bool)
-> (PropertyName -> PropertyName -> Bool) -> Eq PropertyName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PropertyName -> PropertyName -> Bool
$c/= :: PropertyName -> PropertyName -> Bool
== :: PropertyName -> PropertyName -> Bool
$c== :: PropertyName -> PropertyName -> Bool
Eq, Eq PropertyName
Eq PropertyName
-> (PropertyName -> PropertyName -> Ordering)
-> (PropertyName -> PropertyName -> Bool)
-> (PropertyName -> PropertyName -> Bool)
-> (PropertyName -> PropertyName -> Bool)
-> (PropertyName -> PropertyName -> Bool)
-> (PropertyName -> PropertyName -> PropertyName)
-> (PropertyName -> PropertyName -> PropertyName)
-> Ord PropertyName
PropertyName -> PropertyName -> Bool
PropertyName -> PropertyName -> Ordering
PropertyName -> PropertyName -> PropertyName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PropertyName -> PropertyName -> PropertyName
$cmin :: PropertyName -> PropertyName -> PropertyName
max :: PropertyName -> PropertyName -> PropertyName
$cmax :: PropertyName -> PropertyName -> PropertyName
>= :: PropertyName -> PropertyName -> Bool
$c>= :: PropertyName -> PropertyName -> Bool
> :: PropertyName -> PropertyName -> Bool
$c> :: PropertyName -> PropertyName -> Bool
<= :: PropertyName -> PropertyName -> Bool
$c<= :: PropertyName -> PropertyName -> Bool
< :: PropertyName -> PropertyName -> Bool
$c< :: PropertyName -> PropertyName -> Bool
compare :: PropertyName -> PropertyName -> Ordering
$ccompare :: PropertyName -> PropertyName -> Ordering
$cp1Ord :: Eq PropertyName
Ord, Int -> PropertyName -> ShowS
[PropertyName] -> ShowS
PropertyName -> String
(Int -> PropertyName -> ShowS)
-> (PropertyName -> String)
-> ([PropertyName] -> ShowS)
-> Show PropertyName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PropertyName] -> ShowS
$cshowList :: [PropertyName] -> ShowS
show :: PropertyName -> String
$cshow :: PropertyName -> String
showsPrec :: Int -> PropertyName -> ShowS
$cshowsPrec :: Int -> PropertyName -> ShowS
Show, String -> PropertyName
(String -> PropertyName) -> IsString PropertyName
forall a. (String -> a) -> IsString a
fromString :: String -> PropertyName
$cfromString :: String -> PropertyName
IsString, b -> PropertyName -> PropertyName
NonEmpty PropertyName -> PropertyName
PropertyName -> PropertyName -> PropertyName
(PropertyName -> PropertyName -> PropertyName)
-> (NonEmpty PropertyName -> PropertyName)
-> (forall b. Integral b => b -> PropertyName -> PropertyName)
-> Semigroup PropertyName
forall b. Integral b => b -> PropertyName -> PropertyName
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> PropertyName -> PropertyName
$cstimes :: forall b. Integral b => b -> PropertyName -> PropertyName
sconcat :: NonEmpty PropertyName -> PropertyName
$csconcat :: NonEmpty PropertyName -> PropertyName
<> :: PropertyName -> PropertyName -> PropertyName
$c<> :: PropertyName -> PropertyName -> PropertyName
Semigroup, PropertyName -> Q Exp
PropertyName -> Q (TExp PropertyName)
(PropertyName -> Q Exp)
-> (PropertyName -> Q (TExp PropertyName)) -> Lift PropertyName
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: PropertyName -> Q (TExp PropertyName)
$cliftTyped :: PropertyName -> Q (TExp PropertyName)
lift :: PropertyName -> Q Exp
$clift :: PropertyName -> Q Exp
Lift)

-- | The acceptable occurrence of false positives
--
--   Example, @Confidence 10^9@ would mean that you'd accept a false positive
--   for 1 in 10^9 tests.
newtype Confidence =
  Confidence {
    Confidence -> Int64
unConfidence :: Int64
  } deriving (Confidence -> Confidence -> Bool
(Confidence -> Confidence -> Bool)
-> (Confidence -> Confidence -> Bool) -> Eq Confidence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Confidence -> Confidence -> Bool
$c/= :: Confidence -> Confidence -> Bool
== :: Confidence -> Confidence -> Bool
$c== :: Confidence -> Confidence -> Bool
Eq, Eq Confidence
Eq Confidence
-> (Confidence -> Confidence -> Ordering)
-> (Confidence -> Confidence -> Bool)
-> (Confidence -> Confidence -> Bool)
-> (Confidence -> Confidence -> Bool)
-> (Confidence -> Confidence -> Bool)
-> (Confidence -> Confidence -> Confidence)
-> (Confidence -> Confidence -> Confidence)
-> Ord Confidence
Confidence -> Confidence -> Bool
Confidence -> Confidence -> Ordering
Confidence -> Confidence -> Confidence
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Confidence -> Confidence -> Confidence
$cmin :: Confidence -> Confidence -> Confidence
max :: Confidence -> Confidence -> Confidence
$cmax :: Confidence -> Confidence -> Confidence
>= :: Confidence -> Confidence -> Bool
$c>= :: Confidence -> Confidence -> Bool
> :: Confidence -> Confidence -> Bool
$c> :: Confidence -> Confidence -> Bool
<= :: Confidence -> Confidence -> Bool
$c<= :: Confidence -> Confidence -> Bool
< :: Confidence -> Confidence -> Bool
$c< :: Confidence -> Confidence -> Bool
compare :: Confidence -> Confidence -> Ordering
$ccompare :: Confidence -> Confidence -> Ordering
$cp1Ord :: Eq Confidence
Ord, Int -> Confidence -> ShowS
[Confidence] -> ShowS
Confidence -> String
(Int -> Confidence -> ShowS)
-> (Confidence -> String)
-> ([Confidence] -> ShowS)
-> Show Confidence
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Confidence] -> ShowS
$cshowList :: [Confidence] -> ShowS
show :: Confidence -> String
$cshow :: Confidence -> String
showsPrec :: Int -> Confidence -> ShowS
$cshowsPrec :: Int -> Confidence -> ShowS
Show, Integer -> Confidence
Confidence -> Confidence
Confidence -> Confidence -> Confidence
(Confidence -> Confidence -> Confidence)
-> (Confidence -> Confidence -> Confidence)
-> (Confidence -> Confidence -> Confidence)
-> (Confidence -> Confidence)
-> (Confidence -> Confidence)
-> (Confidence -> Confidence)
-> (Integer -> Confidence)
-> Num Confidence
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Confidence
$cfromInteger :: Integer -> Confidence
signum :: Confidence -> Confidence
$csignum :: Confidence -> Confidence
abs :: Confidence -> Confidence
$cabs :: Confidence -> Confidence
negate :: Confidence -> Confidence
$cnegate :: Confidence -> Confidence
* :: Confidence -> Confidence -> Confidence
$c* :: Confidence -> Confidence -> Confidence
- :: Confidence -> Confidence -> Confidence
$c- :: Confidence -> Confidence -> Confidence
+ :: Confidence -> Confidence -> Confidence
$c+ :: Confidence -> Confidence -> Confidence
Num, Confidence -> Q Exp
Confidence -> Q (TExp Confidence)
(Confidence -> Q Exp)
-> (Confidence -> Q (TExp Confidence)) -> Lift Confidence
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: Confidence -> Q (TExp Confidence)
$cliftTyped :: Confidence -> Q (TExp Confidence)
lift :: Confidence -> Q Exp
$clift :: Confidence -> Q Exp
Lift)

-- | Configuration for a property test.
--
data PropertyConfig =
  PropertyConfig {
      PropertyConfig -> DiscardLimit
propertyDiscardLimit :: !DiscardLimit
    , PropertyConfig -> ShrinkLimit
propertyShrinkLimit :: !ShrinkLimit
    , PropertyConfig -> ShrinkRetries
propertyShrinkRetries :: !ShrinkRetries
    , PropertyConfig -> TerminationCriteria
propertyTerminationCriteria :: !TerminationCriteria
    } deriving (PropertyConfig -> PropertyConfig -> Bool
(PropertyConfig -> PropertyConfig -> Bool)
-> (PropertyConfig -> PropertyConfig -> Bool) -> Eq PropertyConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PropertyConfig -> PropertyConfig -> Bool
$c/= :: PropertyConfig -> PropertyConfig -> Bool
== :: PropertyConfig -> PropertyConfig -> Bool
$c== :: PropertyConfig -> PropertyConfig -> Bool
Eq, Eq PropertyConfig
Eq PropertyConfig
-> (PropertyConfig -> PropertyConfig -> Ordering)
-> (PropertyConfig -> PropertyConfig -> Bool)
-> (PropertyConfig -> PropertyConfig -> Bool)
-> (PropertyConfig -> PropertyConfig -> Bool)
-> (PropertyConfig -> PropertyConfig -> Bool)
-> (PropertyConfig -> PropertyConfig -> PropertyConfig)
-> (PropertyConfig -> PropertyConfig -> PropertyConfig)
-> Ord PropertyConfig
PropertyConfig -> PropertyConfig -> Bool
PropertyConfig -> PropertyConfig -> Ordering
PropertyConfig -> PropertyConfig -> PropertyConfig
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PropertyConfig -> PropertyConfig -> PropertyConfig
$cmin :: PropertyConfig -> PropertyConfig -> PropertyConfig
max :: PropertyConfig -> PropertyConfig -> PropertyConfig
$cmax :: PropertyConfig -> PropertyConfig -> PropertyConfig
>= :: PropertyConfig -> PropertyConfig -> Bool
$c>= :: PropertyConfig -> PropertyConfig -> Bool
> :: PropertyConfig -> PropertyConfig -> Bool
$c> :: PropertyConfig -> PropertyConfig -> Bool
<= :: PropertyConfig -> PropertyConfig -> Bool
$c<= :: PropertyConfig -> PropertyConfig -> Bool
< :: PropertyConfig -> PropertyConfig -> Bool
$c< :: PropertyConfig -> PropertyConfig -> Bool
compare :: PropertyConfig -> PropertyConfig -> Ordering
$ccompare :: PropertyConfig -> PropertyConfig -> Ordering
$cp1Ord :: Eq PropertyConfig
Ord, Int -> PropertyConfig -> ShowS
[PropertyConfig] -> ShowS
PropertyConfig -> String
(Int -> PropertyConfig -> ShowS)
-> (PropertyConfig -> String)
-> ([PropertyConfig] -> ShowS)
-> Show PropertyConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PropertyConfig] -> ShowS
$cshowList :: [PropertyConfig] -> ShowS
show :: PropertyConfig -> String
$cshow :: PropertyConfig -> String
showsPrec :: Int -> PropertyConfig -> ShowS
$cshowsPrec :: Int -> PropertyConfig -> ShowS
Show, PropertyConfig -> Q Exp
PropertyConfig -> Q (TExp PropertyConfig)
(PropertyConfig -> Q Exp)
-> (PropertyConfig -> Q (TExp PropertyConfig))
-> Lift PropertyConfig
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: PropertyConfig -> Q (TExp PropertyConfig)
$cliftTyped :: PropertyConfig -> Q (TExp PropertyConfig)
lift :: PropertyConfig -> Q Exp
$clift :: PropertyConfig -> Q Exp
Lift)

-- | The number of successful tests that need to be run before a property test
--   is considered successful.
--
--   Can be constructed using numeric literals:
--
-- @
--   200 :: TestLimit
-- @
--
newtype TestLimit =
  TestLimit Int
  deriving (TestLimit -> TestLimit -> Bool
(TestLimit -> TestLimit -> Bool)
-> (TestLimit -> TestLimit -> Bool) -> Eq TestLimit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestLimit -> TestLimit -> Bool
$c/= :: TestLimit -> TestLimit -> Bool
== :: TestLimit -> TestLimit -> Bool
$c== :: TestLimit -> TestLimit -> Bool
Eq, Eq TestLimit
Eq TestLimit
-> (TestLimit -> TestLimit -> Ordering)
-> (TestLimit -> TestLimit -> Bool)
-> (TestLimit -> TestLimit -> Bool)
-> (TestLimit -> TestLimit -> Bool)
-> (TestLimit -> TestLimit -> Bool)
-> (TestLimit -> TestLimit -> TestLimit)
-> (TestLimit -> TestLimit -> TestLimit)
-> Ord TestLimit
TestLimit -> TestLimit -> Bool
TestLimit -> TestLimit -> Ordering
TestLimit -> TestLimit -> TestLimit
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TestLimit -> TestLimit -> TestLimit
$cmin :: TestLimit -> TestLimit -> TestLimit
max :: TestLimit -> TestLimit -> TestLimit
$cmax :: TestLimit -> TestLimit -> TestLimit
>= :: TestLimit -> TestLimit -> Bool
$c>= :: TestLimit -> TestLimit -> Bool
> :: TestLimit -> TestLimit -> Bool
$c> :: TestLimit -> TestLimit -> Bool
<= :: TestLimit -> TestLimit -> Bool
$c<= :: TestLimit -> TestLimit -> Bool
< :: TestLimit -> TestLimit -> Bool
$c< :: TestLimit -> TestLimit -> Bool
compare :: TestLimit -> TestLimit -> Ordering
$ccompare :: TestLimit -> TestLimit -> Ordering
$cp1Ord :: Eq TestLimit
Ord, Int -> TestLimit -> ShowS
[TestLimit] -> ShowS
TestLimit -> String
(Int -> TestLimit -> ShowS)
-> (TestLimit -> String)
-> ([TestLimit] -> ShowS)
-> Show TestLimit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestLimit] -> ShowS
$cshowList :: [TestLimit] -> ShowS
show :: TestLimit -> String
$cshow :: TestLimit -> String
showsPrec :: Int -> TestLimit -> ShowS
$cshowsPrec :: Int -> TestLimit -> ShowS
Show, Integer -> TestLimit
TestLimit -> TestLimit
TestLimit -> TestLimit -> TestLimit
(TestLimit -> TestLimit -> TestLimit)
-> (TestLimit -> TestLimit -> TestLimit)
-> (TestLimit -> TestLimit -> TestLimit)
-> (TestLimit -> TestLimit)
-> (TestLimit -> TestLimit)
-> (TestLimit -> TestLimit)
-> (Integer -> TestLimit)
-> Num TestLimit
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> TestLimit
$cfromInteger :: Integer -> TestLimit
signum :: TestLimit -> TestLimit
$csignum :: TestLimit -> TestLimit
abs :: TestLimit -> TestLimit
$cabs :: TestLimit -> TestLimit
negate :: TestLimit -> TestLimit
$cnegate :: TestLimit -> TestLimit
* :: TestLimit -> TestLimit -> TestLimit
$c* :: TestLimit -> TestLimit -> TestLimit
- :: TestLimit -> TestLimit -> TestLimit
$c- :: TestLimit -> TestLimit -> TestLimit
+ :: TestLimit -> TestLimit -> TestLimit
$c+ :: TestLimit -> TestLimit -> TestLimit
Num, Int -> TestLimit
TestLimit -> Int
TestLimit -> [TestLimit]
TestLimit -> TestLimit
TestLimit -> TestLimit -> [TestLimit]
TestLimit -> TestLimit -> TestLimit -> [TestLimit]
(TestLimit -> TestLimit)
-> (TestLimit -> TestLimit)
-> (Int -> TestLimit)
-> (TestLimit -> Int)
-> (TestLimit -> [TestLimit])
-> (TestLimit -> TestLimit -> [TestLimit])
-> (TestLimit -> TestLimit -> [TestLimit])
-> (TestLimit -> TestLimit -> TestLimit -> [TestLimit])
-> Enum TestLimit
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: TestLimit -> TestLimit -> TestLimit -> [TestLimit]
$cenumFromThenTo :: TestLimit -> TestLimit -> TestLimit -> [TestLimit]
enumFromTo :: TestLimit -> TestLimit -> [TestLimit]
$cenumFromTo :: TestLimit -> TestLimit -> [TestLimit]
enumFromThen :: TestLimit -> TestLimit -> [TestLimit]
$cenumFromThen :: TestLimit -> TestLimit -> [TestLimit]
enumFrom :: TestLimit -> [TestLimit]
$cenumFrom :: TestLimit -> [TestLimit]
fromEnum :: TestLimit -> Int
$cfromEnum :: TestLimit -> Int
toEnum :: Int -> TestLimit
$ctoEnum :: Int -> TestLimit
pred :: TestLimit -> TestLimit
$cpred :: TestLimit -> TestLimit
succ :: TestLimit -> TestLimit
$csucc :: TestLimit -> TestLimit
Enum, Num TestLimit
Ord TestLimit
Num TestLimit
-> Ord TestLimit -> (TestLimit -> Rational) -> Real TestLimit
TestLimit -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: TestLimit -> Rational
$ctoRational :: TestLimit -> Rational
$cp2Real :: Ord TestLimit
$cp1Real :: Num TestLimit
Real, Enum TestLimit
Real TestLimit
Real TestLimit
-> Enum TestLimit
-> (TestLimit -> TestLimit -> TestLimit)
-> (TestLimit -> TestLimit -> TestLimit)
-> (TestLimit -> TestLimit -> TestLimit)
-> (TestLimit -> TestLimit -> TestLimit)
-> (TestLimit -> TestLimit -> (TestLimit, TestLimit))
-> (TestLimit -> TestLimit -> (TestLimit, TestLimit))
-> (TestLimit -> Integer)
-> Integral TestLimit
TestLimit -> Integer
TestLimit -> TestLimit -> (TestLimit, TestLimit)
TestLimit -> TestLimit -> TestLimit
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: TestLimit -> Integer
$ctoInteger :: TestLimit -> Integer
divMod :: TestLimit -> TestLimit -> (TestLimit, TestLimit)
$cdivMod :: TestLimit -> TestLimit -> (TestLimit, TestLimit)
quotRem :: TestLimit -> TestLimit -> (TestLimit, TestLimit)
$cquotRem :: TestLimit -> TestLimit -> (TestLimit, TestLimit)
mod :: TestLimit -> TestLimit -> TestLimit
$cmod :: TestLimit -> TestLimit -> TestLimit
div :: TestLimit -> TestLimit -> TestLimit
$cdiv :: TestLimit -> TestLimit -> TestLimit
rem :: TestLimit -> TestLimit -> TestLimit
$crem :: TestLimit -> TestLimit -> TestLimit
quot :: TestLimit -> TestLimit -> TestLimit
$cquot :: TestLimit -> TestLimit -> TestLimit
$cp2Integral :: Enum TestLimit
$cp1Integral :: Real TestLimit
Integral, TestLimit -> Q Exp
TestLimit -> Q (TExp TestLimit)
(TestLimit -> Q Exp)
-> (TestLimit -> Q (TExp TestLimit)) -> Lift TestLimit
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: TestLimit -> Q (TExp TestLimit)
$cliftTyped :: TestLimit -> Q (TExp TestLimit)
lift :: TestLimit -> Q Exp
$clift :: TestLimit -> Q Exp
Lift)

-- | The number of tests a property ran successfully.
--
newtype TestCount =
  TestCount Int
  deriving (TestCount -> TestCount -> Bool
(TestCount -> TestCount -> Bool)
-> (TestCount -> TestCount -> Bool) -> Eq TestCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestCount -> TestCount -> Bool
$c/= :: TestCount -> TestCount -> Bool
== :: TestCount -> TestCount -> Bool
$c== :: TestCount -> TestCount -> Bool
Eq, Eq TestCount
Eq TestCount
-> (TestCount -> TestCount -> Ordering)
-> (TestCount -> TestCount -> Bool)
-> (TestCount -> TestCount -> Bool)
-> (TestCount -> TestCount -> Bool)
-> (TestCount -> TestCount -> Bool)
-> (TestCount -> TestCount -> TestCount)
-> (TestCount -> TestCount -> TestCount)
-> Ord TestCount
TestCount -> TestCount -> Bool
TestCount -> TestCount -> Ordering
TestCount -> TestCount -> TestCount
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TestCount -> TestCount -> TestCount
$cmin :: TestCount -> TestCount -> TestCount
max :: TestCount -> TestCount -> TestCount
$cmax :: TestCount -> TestCount -> TestCount
>= :: TestCount -> TestCount -> Bool
$c>= :: TestCount -> TestCount -> Bool
> :: TestCount -> TestCount -> Bool
$c> :: TestCount -> TestCount -> Bool
<= :: TestCount -> TestCount -> Bool
$c<= :: TestCount -> TestCount -> Bool
< :: TestCount -> TestCount -> Bool
$c< :: TestCount -> TestCount -> Bool
compare :: TestCount -> TestCount -> Ordering
$ccompare :: TestCount -> TestCount -> Ordering
$cp1Ord :: Eq TestCount
Ord, Int -> TestCount -> ShowS
[TestCount] -> ShowS
TestCount -> String
(Int -> TestCount -> ShowS)
-> (TestCount -> String)
-> ([TestCount] -> ShowS)
-> Show TestCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestCount] -> ShowS
$cshowList :: [TestCount] -> ShowS
show :: TestCount -> String
$cshow :: TestCount -> String
showsPrec :: Int -> TestCount -> ShowS
$cshowsPrec :: Int -> TestCount -> ShowS
Show, Integer -> TestCount
TestCount -> TestCount
TestCount -> TestCount -> TestCount
(TestCount -> TestCount -> TestCount)
-> (TestCount -> TestCount -> TestCount)
-> (TestCount -> TestCount -> TestCount)
-> (TestCount -> TestCount)
-> (TestCount -> TestCount)
-> (TestCount -> TestCount)
-> (Integer -> TestCount)
-> Num TestCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> TestCount
$cfromInteger :: Integer -> TestCount
signum :: TestCount -> TestCount
$csignum :: TestCount -> TestCount
abs :: TestCount -> TestCount
$cabs :: TestCount -> TestCount
negate :: TestCount -> TestCount
$cnegate :: TestCount -> TestCount
* :: TestCount -> TestCount -> TestCount
$c* :: TestCount -> TestCount -> TestCount
- :: TestCount -> TestCount -> TestCount
$c- :: TestCount -> TestCount -> TestCount
+ :: TestCount -> TestCount -> TestCount
$c+ :: TestCount -> TestCount -> TestCount
Num, Int -> TestCount
TestCount -> Int
TestCount -> [TestCount]
TestCount -> TestCount
TestCount -> TestCount -> [TestCount]
TestCount -> TestCount -> TestCount -> [TestCount]
(TestCount -> TestCount)
-> (TestCount -> TestCount)
-> (Int -> TestCount)
-> (TestCount -> Int)
-> (TestCount -> [TestCount])
-> (TestCount -> TestCount -> [TestCount])
-> (TestCount -> TestCount -> [TestCount])
-> (TestCount -> TestCount -> TestCount -> [TestCount])
-> Enum TestCount
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: TestCount -> TestCount -> TestCount -> [TestCount]
$cenumFromThenTo :: TestCount -> TestCount -> TestCount -> [TestCount]
enumFromTo :: TestCount -> TestCount -> [TestCount]
$cenumFromTo :: TestCount -> TestCount -> [TestCount]
enumFromThen :: TestCount -> TestCount -> [TestCount]
$cenumFromThen :: TestCount -> TestCount -> [TestCount]
enumFrom :: TestCount -> [TestCount]
$cenumFrom :: TestCount -> [TestCount]
fromEnum :: TestCount -> Int
$cfromEnum :: TestCount -> Int
toEnum :: Int -> TestCount
$ctoEnum :: Int -> TestCount
pred :: TestCount -> TestCount
$cpred :: TestCount -> TestCount
succ :: TestCount -> TestCount
$csucc :: TestCount -> TestCount
Enum, Num TestCount
Ord TestCount
Num TestCount
-> Ord TestCount -> (TestCount -> Rational) -> Real TestCount
TestCount -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: TestCount -> Rational
$ctoRational :: TestCount -> Rational
$cp2Real :: Ord TestCount
$cp1Real :: Num TestCount
Real, Enum TestCount
Real TestCount
Real TestCount
-> Enum TestCount
-> (TestCount -> TestCount -> TestCount)
-> (TestCount -> TestCount -> TestCount)
-> (TestCount -> TestCount -> TestCount)
-> (TestCount -> TestCount -> TestCount)
-> (TestCount -> TestCount -> (TestCount, TestCount))
-> (TestCount -> TestCount -> (TestCount, TestCount))
-> (TestCount -> Integer)
-> Integral TestCount
TestCount -> Integer
TestCount -> TestCount -> (TestCount, TestCount)
TestCount -> TestCount -> TestCount
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: TestCount -> Integer
$ctoInteger :: TestCount -> Integer
divMod :: TestCount -> TestCount -> (TestCount, TestCount)
$cdivMod :: TestCount -> TestCount -> (TestCount, TestCount)
quotRem :: TestCount -> TestCount -> (TestCount, TestCount)
$cquotRem :: TestCount -> TestCount -> (TestCount, TestCount)
mod :: TestCount -> TestCount -> TestCount
$cmod :: TestCount -> TestCount -> TestCount
div :: TestCount -> TestCount -> TestCount
$cdiv :: TestCount -> TestCount -> TestCount
rem :: TestCount -> TestCount -> TestCount
$crem :: TestCount -> TestCount -> TestCount
quot :: TestCount -> TestCount -> TestCount
$cquot :: TestCount -> TestCount -> TestCount
$cp2Integral :: Enum TestCount
$cp1Integral :: Real TestCount
Integral)

-- | The number of tests a property had to discard.
--
newtype DiscardCount =
  DiscardCount Int
  deriving (DiscardCount -> DiscardCount -> Bool
(DiscardCount -> DiscardCount -> Bool)
-> (DiscardCount -> DiscardCount -> Bool) -> Eq DiscardCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DiscardCount -> DiscardCount -> Bool
$c/= :: DiscardCount -> DiscardCount -> Bool
== :: DiscardCount -> DiscardCount -> Bool
$c== :: DiscardCount -> DiscardCount -> Bool
Eq, Eq DiscardCount
Eq DiscardCount
-> (DiscardCount -> DiscardCount -> Ordering)
-> (DiscardCount -> DiscardCount -> Bool)
-> (DiscardCount -> DiscardCount -> Bool)
-> (DiscardCount -> DiscardCount -> Bool)
-> (DiscardCount -> DiscardCount -> Bool)
-> (DiscardCount -> DiscardCount -> DiscardCount)
-> (DiscardCount -> DiscardCount -> DiscardCount)
-> Ord DiscardCount
DiscardCount -> DiscardCount -> Bool
DiscardCount -> DiscardCount -> Ordering
DiscardCount -> DiscardCount -> DiscardCount
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DiscardCount -> DiscardCount -> DiscardCount
$cmin :: DiscardCount -> DiscardCount -> DiscardCount
max :: DiscardCount -> DiscardCount -> DiscardCount
$cmax :: DiscardCount -> DiscardCount -> DiscardCount
>= :: DiscardCount -> DiscardCount -> Bool
$c>= :: DiscardCount -> DiscardCount -> Bool
> :: DiscardCount -> DiscardCount -> Bool
$c> :: DiscardCount -> DiscardCount -> Bool
<= :: DiscardCount -> DiscardCount -> Bool
$c<= :: DiscardCount -> DiscardCount -> Bool
< :: DiscardCount -> DiscardCount -> Bool
$c< :: DiscardCount -> DiscardCount -> Bool
compare :: DiscardCount -> DiscardCount -> Ordering
$ccompare :: DiscardCount -> DiscardCount -> Ordering
$cp1Ord :: Eq DiscardCount
Ord, Int -> DiscardCount -> ShowS
[DiscardCount] -> ShowS
DiscardCount -> String
(Int -> DiscardCount -> ShowS)
-> (DiscardCount -> String)
-> ([DiscardCount] -> ShowS)
-> Show DiscardCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DiscardCount] -> ShowS
$cshowList :: [DiscardCount] -> ShowS
show :: DiscardCount -> String
$cshow :: DiscardCount -> String
showsPrec :: Int -> DiscardCount -> ShowS
$cshowsPrec :: Int -> DiscardCount -> ShowS
Show, Integer -> DiscardCount
DiscardCount -> DiscardCount
DiscardCount -> DiscardCount -> DiscardCount
(DiscardCount -> DiscardCount -> DiscardCount)
-> (DiscardCount -> DiscardCount -> DiscardCount)
-> (DiscardCount -> DiscardCount -> DiscardCount)
-> (DiscardCount -> DiscardCount)
-> (DiscardCount -> DiscardCount)
-> (DiscardCount -> DiscardCount)
-> (Integer -> DiscardCount)
-> Num DiscardCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> DiscardCount
$cfromInteger :: Integer -> DiscardCount
signum :: DiscardCount -> DiscardCount
$csignum :: DiscardCount -> DiscardCount
abs :: DiscardCount -> DiscardCount
$cabs :: DiscardCount -> DiscardCount
negate :: DiscardCount -> DiscardCount
$cnegate :: DiscardCount -> DiscardCount
* :: DiscardCount -> DiscardCount -> DiscardCount
$c* :: DiscardCount -> DiscardCount -> DiscardCount
- :: DiscardCount -> DiscardCount -> DiscardCount
$c- :: DiscardCount -> DiscardCount -> DiscardCount
+ :: DiscardCount -> DiscardCount -> DiscardCount
$c+ :: DiscardCount -> DiscardCount -> DiscardCount
Num, Int -> DiscardCount
DiscardCount -> Int
DiscardCount -> [DiscardCount]
DiscardCount -> DiscardCount
DiscardCount -> DiscardCount -> [DiscardCount]
DiscardCount -> DiscardCount -> DiscardCount -> [DiscardCount]
(DiscardCount -> DiscardCount)
-> (DiscardCount -> DiscardCount)
-> (Int -> DiscardCount)
-> (DiscardCount -> Int)
-> (DiscardCount -> [DiscardCount])
-> (DiscardCount -> DiscardCount -> [DiscardCount])
-> (DiscardCount -> DiscardCount -> [DiscardCount])
-> (DiscardCount -> DiscardCount -> DiscardCount -> [DiscardCount])
-> Enum DiscardCount
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: DiscardCount -> DiscardCount -> DiscardCount -> [DiscardCount]
$cenumFromThenTo :: DiscardCount -> DiscardCount -> DiscardCount -> [DiscardCount]
enumFromTo :: DiscardCount -> DiscardCount -> [DiscardCount]
$cenumFromTo :: DiscardCount -> DiscardCount -> [DiscardCount]
enumFromThen :: DiscardCount -> DiscardCount -> [DiscardCount]
$cenumFromThen :: DiscardCount -> DiscardCount -> [DiscardCount]
enumFrom :: DiscardCount -> [DiscardCount]
$cenumFrom :: DiscardCount -> [DiscardCount]
fromEnum :: DiscardCount -> Int
$cfromEnum :: DiscardCount -> Int
toEnum :: Int -> DiscardCount
$ctoEnum :: Int -> DiscardCount
pred :: DiscardCount -> DiscardCount
$cpred :: DiscardCount -> DiscardCount
succ :: DiscardCount -> DiscardCount
$csucc :: DiscardCount -> DiscardCount
Enum, Num DiscardCount
Ord DiscardCount
Num DiscardCount
-> Ord DiscardCount
-> (DiscardCount -> Rational)
-> Real DiscardCount
DiscardCount -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: DiscardCount -> Rational
$ctoRational :: DiscardCount -> Rational
$cp2Real :: Ord DiscardCount
$cp1Real :: Num DiscardCount
Real, Enum DiscardCount
Real DiscardCount
Real DiscardCount
-> Enum DiscardCount
-> (DiscardCount -> DiscardCount -> DiscardCount)
-> (DiscardCount -> DiscardCount -> DiscardCount)
-> (DiscardCount -> DiscardCount -> DiscardCount)
-> (DiscardCount -> DiscardCount -> DiscardCount)
-> (DiscardCount -> DiscardCount -> (DiscardCount, DiscardCount))
-> (DiscardCount -> DiscardCount -> (DiscardCount, DiscardCount))
-> (DiscardCount -> Integer)
-> Integral DiscardCount
DiscardCount -> Integer
DiscardCount -> DiscardCount -> (DiscardCount, DiscardCount)
DiscardCount -> DiscardCount -> DiscardCount
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: DiscardCount -> Integer
$ctoInteger :: DiscardCount -> Integer
divMod :: DiscardCount -> DiscardCount -> (DiscardCount, DiscardCount)
$cdivMod :: DiscardCount -> DiscardCount -> (DiscardCount, DiscardCount)
quotRem :: DiscardCount -> DiscardCount -> (DiscardCount, DiscardCount)
$cquotRem :: DiscardCount -> DiscardCount -> (DiscardCount, DiscardCount)
mod :: DiscardCount -> DiscardCount -> DiscardCount
$cmod :: DiscardCount -> DiscardCount -> DiscardCount
div :: DiscardCount -> DiscardCount -> DiscardCount
$cdiv :: DiscardCount -> DiscardCount -> DiscardCount
rem :: DiscardCount -> DiscardCount -> DiscardCount
$crem :: DiscardCount -> DiscardCount -> DiscardCount
quot :: DiscardCount -> DiscardCount -> DiscardCount
$cquot :: DiscardCount -> DiscardCount -> DiscardCount
$cp2Integral :: Enum DiscardCount
$cp1Integral :: Real DiscardCount
Integral)

-- | The number of discards to allow before giving up.
--
--   Can be constructed using numeric literals:
--
-- @
--   10000 :: DiscardLimit
-- @
--
--
newtype DiscardLimit =
  DiscardLimit Int
  deriving (DiscardLimit -> DiscardLimit -> Bool
(DiscardLimit -> DiscardLimit -> Bool)
-> (DiscardLimit -> DiscardLimit -> Bool) -> Eq DiscardLimit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DiscardLimit -> DiscardLimit -> Bool
$c/= :: DiscardLimit -> DiscardLimit -> Bool
== :: DiscardLimit -> DiscardLimit -> Bool
$c== :: DiscardLimit -> DiscardLimit -> Bool
Eq, Eq DiscardLimit
Eq DiscardLimit
-> (DiscardLimit -> DiscardLimit -> Ordering)
-> (DiscardLimit -> DiscardLimit -> Bool)
-> (DiscardLimit -> DiscardLimit -> Bool)
-> (DiscardLimit -> DiscardLimit -> Bool)
-> (DiscardLimit -> DiscardLimit -> Bool)
-> (DiscardLimit -> DiscardLimit -> DiscardLimit)
-> (DiscardLimit -> DiscardLimit -> DiscardLimit)
-> Ord DiscardLimit
DiscardLimit -> DiscardLimit -> Bool
DiscardLimit -> DiscardLimit -> Ordering
DiscardLimit -> DiscardLimit -> DiscardLimit
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DiscardLimit -> DiscardLimit -> DiscardLimit
$cmin :: DiscardLimit -> DiscardLimit -> DiscardLimit
max :: DiscardLimit -> DiscardLimit -> DiscardLimit
$cmax :: DiscardLimit -> DiscardLimit -> DiscardLimit
>= :: DiscardLimit -> DiscardLimit -> Bool
$c>= :: DiscardLimit -> DiscardLimit -> Bool
> :: DiscardLimit -> DiscardLimit -> Bool
$c> :: DiscardLimit -> DiscardLimit -> Bool
<= :: DiscardLimit -> DiscardLimit -> Bool
$c<= :: DiscardLimit -> DiscardLimit -> Bool
< :: DiscardLimit -> DiscardLimit -> Bool
$c< :: DiscardLimit -> DiscardLimit -> Bool
compare :: DiscardLimit -> DiscardLimit -> Ordering
$ccompare :: DiscardLimit -> DiscardLimit -> Ordering
$cp1Ord :: Eq DiscardLimit
Ord, Int -> DiscardLimit -> ShowS
[DiscardLimit] -> ShowS
DiscardLimit -> String
(Int -> DiscardLimit -> ShowS)
-> (DiscardLimit -> String)
-> ([DiscardLimit] -> ShowS)
-> Show DiscardLimit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DiscardLimit] -> ShowS
$cshowList :: [DiscardLimit] -> ShowS
show :: DiscardLimit -> String
$cshow :: DiscardLimit -> String
showsPrec :: Int -> DiscardLimit -> ShowS
$cshowsPrec :: Int -> DiscardLimit -> ShowS
Show, Integer -> DiscardLimit
DiscardLimit -> DiscardLimit
DiscardLimit -> DiscardLimit -> DiscardLimit
(DiscardLimit -> DiscardLimit -> DiscardLimit)
-> (DiscardLimit -> DiscardLimit -> DiscardLimit)
-> (DiscardLimit -> DiscardLimit -> DiscardLimit)
-> (DiscardLimit -> DiscardLimit)
-> (DiscardLimit -> DiscardLimit)
-> (DiscardLimit -> DiscardLimit)
-> (Integer -> DiscardLimit)
-> Num DiscardLimit
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> DiscardLimit
$cfromInteger :: Integer -> DiscardLimit
signum :: DiscardLimit -> DiscardLimit
$csignum :: DiscardLimit -> DiscardLimit
abs :: DiscardLimit -> DiscardLimit
$cabs :: DiscardLimit -> DiscardLimit
negate :: DiscardLimit -> DiscardLimit
$cnegate :: DiscardLimit -> DiscardLimit
* :: DiscardLimit -> DiscardLimit -> DiscardLimit
$c* :: DiscardLimit -> DiscardLimit -> DiscardLimit
- :: DiscardLimit -> DiscardLimit -> DiscardLimit
$c- :: DiscardLimit -> DiscardLimit -> DiscardLimit
+ :: DiscardLimit -> DiscardLimit -> DiscardLimit
$c+ :: DiscardLimit -> DiscardLimit -> DiscardLimit
Num, Int -> DiscardLimit
DiscardLimit -> Int
DiscardLimit -> [DiscardLimit]
DiscardLimit -> DiscardLimit
DiscardLimit -> DiscardLimit -> [DiscardLimit]
DiscardLimit -> DiscardLimit -> DiscardLimit -> [DiscardLimit]
(DiscardLimit -> DiscardLimit)
-> (DiscardLimit -> DiscardLimit)
-> (Int -> DiscardLimit)
-> (DiscardLimit -> Int)
-> (DiscardLimit -> [DiscardLimit])
-> (DiscardLimit -> DiscardLimit -> [DiscardLimit])
-> (DiscardLimit -> DiscardLimit -> [DiscardLimit])
-> (DiscardLimit -> DiscardLimit -> DiscardLimit -> [DiscardLimit])
-> Enum DiscardLimit
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: DiscardLimit -> DiscardLimit -> DiscardLimit -> [DiscardLimit]
$cenumFromThenTo :: DiscardLimit -> DiscardLimit -> DiscardLimit -> [DiscardLimit]
enumFromTo :: DiscardLimit -> DiscardLimit -> [DiscardLimit]
$cenumFromTo :: DiscardLimit -> DiscardLimit -> [DiscardLimit]
enumFromThen :: DiscardLimit -> DiscardLimit -> [DiscardLimit]
$cenumFromThen :: DiscardLimit -> DiscardLimit -> [DiscardLimit]
enumFrom :: DiscardLimit -> [DiscardLimit]
$cenumFrom :: DiscardLimit -> [DiscardLimit]
fromEnum :: DiscardLimit -> Int
$cfromEnum :: DiscardLimit -> Int
toEnum :: Int -> DiscardLimit
$ctoEnum :: Int -> DiscardLimit
pred :: DiscardLimit -> DiscardLimit
$cpred :: DiscardLimit -> DiscardLimit
succ :: DiscardLimit -> DiscardLimit
$csucc :: DiscardLimit -> DiscardLimit
Enum, Num DiscardLimit
Ord DiscardLimit
Num DiscardLimit
-> Ord DiscardLimit
-> (DiscardLimit -> Rational)
-> Real DiscardLimit
DiscardLimit -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: DiscardLimit -> Rational
$ctoRational :: DiscardLimit -> Rational
$cp2Real :: Ord DiscardLimit
$cp1Real :: Num DiscardLimit
Real, Enum DiscardLimit
Real DiscardLimit
Real DiscardLimit
-> Enum DiscardLimit
-> (DiscardLimit -> DiscardLimit -> DiscardLimit)
-> (DiscardLimit -> DiscardLimit -> DiscardLimit)
-> (DiscardLimit -> DiscardLimit -> DiscardLimit)
-> (DiscardLimit -> DiscardLimit -> DiscardLimit)
-> (DiscardLimit -> DiscardLimit -> (DiscardLimit, DiscardLimit))
-> (DiscardLimit -> DiscardLimit -> (DiscardLimit, DiscardLimit))
-> (DiscardLimit -> Integer)
-> Integral DiscardLimit
DiscardLimit -> Integer
DiscardLimit -> DiscardLimit -> (DiscardLimit, DiscardLimit)
DiscardLimit -> DiscardLimit -> DiscardLimit
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: DiscardLimit -> Integer
$ctoInteger :: DiscardLimit -> Integer
divMod :: DiscardLimit -> DiscardLimit -> (DiscardLimit, DiscardLimit)
$cdivMod :: DiscardLimit -> DiscardLimit -> (DiscardLimit, DiscardLimit)
quotRem :: DiscardLimit -> DiscardLimit -> (DiscardLimit, DiscardLimit)
$cquotRem :: DiscardLimit -> DiscardLimit -> (DiscardLimit, DiscardLimit)
mod :: DiscardLimit -> DiscardLimit -> DiscardLimit
$cmod :: DiscardLimit -> DiscardLimit -> DiscardLimit
div :: DiscardLimit -> DiscardLimit -> DiscardLimit
$cdiv :: DiscardLimit -> DiscardLimit -> DiscardLimit
rem :: DiscardLimit -> DiscardLimit -> DiscardLimit
$crem :: DiscardLimit -> DiscardLimit -> DiscardLimit
quot :: DiscardLimit -> DiscardLimit -> DiscardLimit
$cquot :: DiscardLimit -> DiscardLimit -> DiscardLimit
$cp2Integral :: Enum DiscardLimit
$cp1Integral :: Real DiscardLimit
Integral, DiscardLimit -> Q Exp
DiscardLimit -> Q (TExp DiscardLimit)
(DiscardLimit -> Q Exp)
-> (DiscardLimit -> Q (TExp DiscardLimit)) -> Lift DiscardLimit
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: DiscardLimit -> Q (TExp DiscardLimit)
$cliftTyped :: DiscardLimit -> Q (TExp DiscardLimit)
lift :: DiscardLimit -> Q Exp
$clift :: DiscardLimit -> Q Exp
Lift)

-- | The number of shrinks to try before giving up on shrinking.
--
--   Can be constructed using numeric literals:
--
-- @
--   1000 :: ShrinkLimit
-- @
--
newtype ShrinkLimit =
  ShrinkLimit Int
  deriving (ShrinkLimit -> ShrinkLimit -> Bool
(ShrinkLimit -> ShrinkLimit -> Bool)
-> (ShrinkLimit -> ShrinkLimit -> Bool) -> Eq ShrinkLimit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShrinkLimit -> ShrinkLimit -> Bool
$c/= :: ShrinkLimit -> ShrinkLimit -> Bool
== :: ShrinkLimit -> ShrinkLimit -> Bool
$c== :: ShrinkLimit -> ShrinkLimit -> Bool
Eq, Eq ShrinkLimit
Eq ShrinkLimit
-> (ShrinkLimit -> ShrinkLimit -> Ordering)
-> (ShrinkLimit -> ShrinkLimit -> Bool)
-> (ShrinkLimit -> ShrinkLimit -> Bool)
-> (ShrinkLimit -> ShrinkLimit -> Bool)
-> (ShrinkLimit -> ShrinkLimit -> Bool)
-> (ShrinkLimit -> ShrinkLimit -> ShrinkLimit)
-> (ShrinkLimit -> ShrinkLimit -> ShrinkLimit)
-> Ord ShrinkLimit
ShrinkLimit -> ShrinkLimit -> Bool
ShrinkLimit -> ShrinkLimit -> Ordering
ShrinkLimit -> ShrinkLimit -> ShrinkLimit
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
$cmin :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
max :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
$cmax :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
>= :: ShrinkLimit -> ShrinkLimit -> Bool
$c>= :: ShrinkLimit -> ShrinkLimit -> Bool
> :: ShrinkLimit -> ShrinkLimit -> Bool
$c> :: ShrinkLimit -> ShrinkLimit -> Bool
<= :: ShrinkLimit -> ShrinkLimit -> Bool
$c<= :: ShrinkLimit -> ShrinkLimit -> Bool
< :: ShrinkLimit -> ShrinkLimit -> Bool
$c< :: ShrinkLimit -> ShrinkLimit -> Bool
compare :: ShrinkLimit -> ShrinkLimit -> Ordering
$ccompare :: ShrinkLimit -> ShrinkLimit -> Ordering
$cp1Ord :: Eq ShrinkLimit
Ord, Int -> ShrinkLimit -> ShowS
[ShrinkLimit] -> ShowS
ShrinkLimit -> String
(Int -> ShrinkLimit -> ShowS)
-> (ShrinkLimit -> String)
-> ([ShrinkLimit] -> ShowS)
-> Show ShrinkLimit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShrinkLimit] -> ShowS
$cshowList :: [ShrinkLimit] -> ShowS
show :: ShrinkLimit -> String
$cshow :: ShrinkLimit -> String
showsPrec :: Int -> ShrinkLimit -> ShowS
$cshowsPrec :: Int -> ShrinkLimit -> ShowS
Show, Integer -> ShrinkLimit
ShrinkLimit -> ShrinkLimit
ShrinkLimit -> ShrinkLimit -> ShrinkLimit
(ShrinkLimit -> ShrinkLimit -> ShrinkLimit)
-> (ShrinkLimit -> ShrinkLimit -> ShrinkLimit)
-> (ShrinkLimit -> ShrinkLimit -> ShrinkLimit)
-> (ShrinkLimit -> ShrinkLimit)
-> (ShrinkLimit -> ShrinkLimit)
-> (ShrinkLimit -> ShrinkLimit)
-> (Integer -> ShrinkLimit)
-> Num ShrinkLimit
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ShrinkLimit
$cfromInteger :: Integer -> ShrinkLimit
signum :: ShrinkLimit -> ShrinkLimit
$csignum :: ShrinkLimit -> ShrinkLimit
abs :: ShrinkLimit -> ShrinkLimit
$cabs :: ShrinkLimit -> ShrinkLimit
negate :: ShrinkLimit -> ShrinkLimit
$cnegate :: ShrinkLimit -> ShrinkLimit
* :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
$c* :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
- :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
$c- :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
+ :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
$c+ :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
Num, Int -> ShrinkLimit
ShrinkLimit -> Int
ShrinkLimit -> [ShrinkLimit]
ShrinkLimit -> ShrinkLimit
ShrinkLimit -> ShrinkLimit -> [ShrinkLimit]
ShrinkLimit -> ShrinkLimit -> ShrinkLimit -> [ShrinkLimit]
(ShrinkLimit -> ShrinkLimit)
-> (ShrinkLimit -> ShrinkLimit)
-> (Int -> ShrinkLimit)
-> (ShrinkLimit -> Int)
-> (ShrinkLimit -> [ShrinkLimit])
-> (ShrinkLimit -> ShrinkLimit -> [ShrinkLimit])
-> (ShrinkLimit -> ShrinkLimit -> [ShrinkLimit])
-> (ShrinkLimit -> ShrinkLimit -> ShrinkLimit -> [ShrinkLimit])
-> Enum ShrinkLimit
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit -> [ShrinkLimit]
$cenumFromThenTo :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit -> [ShrinkLimit]
enumFromTo :: ShrinkLimit -> ShrinkLimit -> [ShrinkLimit]
$cenumFromTo :: ShrinkLimit -> ShrinkLimit -> [ShrinkLimit]
enumFromThen :: ShrinkLimit -> ShrinkLimit -> [ShrinkLimit]
$cenumFromThen :: ShrinkLimit -> ShrinkLimit -> [ShrinkLimit]
enumFrom :: ShrinkLimit -> [ShrinkLimit]
$cenumFrom :: ShrinkLimit -> [ShrinkLimit]
fromEnum :: ShrinkLimit -> Int
$cfromEnum :: ShrinkLimit -> Int
toEnum :: Int -> ShrinkLimit
$ctoEnum :: Int -> ShrinkLimit
pred :: ShrinkLimit -> ShrinkLimit
$cpred :: ShrinkLimit -> ShrinkLimit
succ :: ShrinkLimit -> ShrinkLimit
$csucc :: ShrinkLimit -> ShrinkLimit
Enum, Num ShrinkLimit
Ord ShrinkLimit
Num ShrinkLimit
-> Ord ShrinkLimit -> (ShrinkLimit -> Rational) -> Real ShrinkLimit
ShrinkLimit -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: ShrinkLimit -> Rational
$ctoRational :: ShrinkLimit -> Rational
$cp2Real :: Ord ShrinkLimit
$cp1Real :: Num ShrinkLimit
Real, Enum ShrinkLimit
Real ShrinkLimit
Real ShrinkLimit
-> Enum ShrinkLimit
-> (ShrinkLimit -> ShrinkLimit -> ShrinkLimit)
-> (ShrinkLimit -> ShrinkLimit -> ShrinkLimit)
-> (ShrinkLimit -> ShrinkLimit -> ShrinkLimit)
-> (ShrinkLimit -> ShrinkLimit -> ShrinkLimit)
-> (ShrinkLimit -> ShrinkLimit -> (ShrinkLimit, ShrinkLimit))
-> (ShrinkLimit -> ShrinkLimit -> (ShrinkLimit, ShrinkLimit))
-> (ShrinkLimit -> Integer)
-> Integral ShrinkLimit
ShrinkLimit -> Integer
ShrinkLimit -> ShrinkLimit -> (ShrinkLimit, ShrinkLimit)
ShrinkLimit -> ShrinkLimit -> ShrinkLimit
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: ShrinkLimit -> Integer
$ctoInteger :: ShrinkLimit -> Integer
divMod :: ShrinkLimit -> ShrinkLimit -> (ShrinkLimit, ShrinkLimit)
$cdivMod :: ShrinkLimit -> ShrinkLimit -> (ShrinkLimit, ShrinkLimit)
quotRem :: ShrinkLimit -> ShrinkLimit -> (ShrinkLimit, ShrinkLimit)
$cquotRem :: ShrinkLimit -> ShrinkLimit -> (ShrinkLimit, ShrinkLimit)
mod :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
$cmod :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
div :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
$cdiv :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
rem :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
$crem :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
quot :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
$cquot :: ShrinkLimit -> ShrinkLimit -> ShrinkLimit
$cp2Integral :: Enum ShrinkLimit
$cp1Integral :: Real ShrinkLimit
Integral, ShrinkLimit -> Q Exp
ShrinkLimit -> Q (TExp ShrinkLimit)
(ShrinkLimit -> Q Exp)
-> (ShrinkLimit -> Q (TExp ShrinkLimit)) -> Lift ShrinkLimit
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: ShrinkLimit -> Q (TExp ShrinkLimit)
$cliftTyped :: ShrinkLimit -> Q (TExp ShrinkLimit)
lift :: ShrinkLimit -> Q Exp
$clift :: ShrinkLimit -> Q Exp
Lift)

-- | The numbers of times a property was able to shrink after a failing test.
--
newtype ShrinkCount =
  ShrinkCount Int
  deriving (ShrinkCount -> ShrinkCount -> Bool
(ShrinkCount -> ShrinkCount -> Bool)
-> (ShrinkCount -> ShrinkCount -> Bool) -> Eq ShrinkCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShrinkCount -> ShrinkCount -> Bool
$c/= :: ShrinkCount -> ShrinkCount -> Bool
== :: ShrinkCount -> ShrinkCount -> Bool
$c== :: ShrinkCount -> ShrinkCount -> Bool
Eq, Eq ShrinkCount
Eq ShrinkCount
-> (ShrinkCount -> ShrinkCount -> Ordering)
-> (ShrinkCount -> ShrinkCount -> Bool)
-> (ShrinkCount -> ShrinkCount -> Bool)
-> (ShrinkCount -> ShrinkCount -> Bool)
-> (ShrinkCount -> ShrinkCount -> Bool)
-> (ShrinkCount -> ShrinkCount -> ShrinkCount)
-> (ShrinkCount -> ShrinkCount -> ShrinkCount)
-> Ord ShrinkCount
ShrinkCount -> ShrinkCount -> Bool
ShrinkCount -> ShrinkCount -> Ordering
ShrinkCount -> ShrinkCount -> ShrinkCount
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ShrinkCount -> ShrinkCount -> ShrinkCount
$cmin :: ShrinkCount -> ShrinkCount -> ShrinkCount
max :: ShrinkCount -> ShrinkCount -> ShrinkCount
$cmax :: ShrinkCount -> ShrinkCount -> ShrinkCount
>= :: ShrinkCount -> ShrinkCount -> Bool
$c>= :: ShrinkCount -> ShrinkCount -> Bool
> :: ShrinkCount -> ShrinkCount -> Bool
$c> :: ShrinkCount -> ShrinkCount -> Bool
<= :: ShrinkCount -> ShrinkCount -> Bool
$c<= :: ShrinkCount -> ShrinkCount -> Bool
< :: ShrinkCount -> ShrinkCount -> Bool
$c< :: ShrinkCount -> ShrinkCount -> Bool
compare :: ShrinkCount -> ShrinkCount -> Ordering
$ccompare :: ShrinkCount -> ShrinkCount -> Ordering
$cp1Ord :: Eq ShrinkCount
Ord, Int -> ShrinkCount -> ShowS
[ShrinkCount] -> ShowS
ShrinkCount -> String
(Int -> ShrinkCount -> ShowS)
-> (ShrinkCount -> String)
-> ([ShrinkCount] -> ShowS)
-> Show ShrinkCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShrinkCount] -> ShowS
$cshowList :: [ShrinkCount] -> ShowS
show :: ShrinkCount -> String
$cshow :: ShrinkCount -> String
showsPrec :: Int -> ShrinkCount -> ShowS
$cshowsPrec :: Int -> ShrinkCount -> ShowS
Show, Integer -> ShrinkCount
ShrinkCount -> ShrinkCount
ShrinkCount -> ShrinkCount -> ShrinkCount
(ShrinkCount -> ShrinkCount -> ShrinkCount)
-> (ShrinkCount -> ShrinkCount -> ShrinkCount)
-> (ShrinkCount -> ShrinkCount -> ShrinkCount)
-> (ShrinkCount -> ShrinkCount)
-> (ShrinkCount -> ShrinkCount)
-> (ShrinkCount -> ShrinkCount)
-> (Integer -> ShrinkCount)
-> Num ShrinkCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ShrinkCount
$cfromInteger :: Integer -> ShrinkCount
signum :: ShrinkCount -> ShrinkCount
$csignum :: ShrinkCount -> ShrinkCount
abs :: ShrinkCount -> ShrinkCount
$cabs :: ShrinkCount -> ShrinkCount
negate :: ShrinkCount -> ShrinkCount
$cnegate :: ShrinkCount -> ShrinkCount
* :: ShrinkCount -> ShrinkCount -> ShrinkCount
$c* :: ShrinkCount -> ShrinkCount -> ShrinkCount
- :: ShrinkCount -> ShrinkCount -> ShrinkCount
$c- :: ShrinkCount -> ShrinkCount -> ShrinkCount
+ :: ShrinkCount -> ShrinkCount -> ShrinkCount
$c+ :: ShrinkCount -> ShrinkCount -> ShrinkCount
Num, Int -> ShrinkCount
ShrinkCount -> Int
ShrinkCount -> [ShrinkCount]
ShrinkCount -> ShrinkCount
ShrinkCount -> ShrinkCount -> [ShrinkCount]
ShrinkCount -> ShrinkCount -> ShrinkCount -> [ShrinkCount]
(ShrinkCount -> ShrinkCount)
-> (ShrinkCount -> ShrinkCount)
-> (Int -> ShrinkCount)
-> (ShrinkCount -> Int)
-> (ShrinkCount -> [ShrinkCount])
-> (ShrinkCount -> ShrinkCount -> [ShrinkCount])
-> (ShrinkCount -> ShrinkCount -> [ShrinkCount])
-> (ShrinkCount -> ShrinkCount -> ShrinkCount -> [ShrinkCount])
-> Enum ShrinkCount
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ShrinkCount -> ShrinkCount -> ShrinkCount -> [ShrinkCount]
$cenumFromThenTo :: ShrinkCount -> ShrinkCount -> ShrinkCount -> [ShrinkCount]
enumFromTo :: ShrinkCount -> ShrinkCount -> [ShrinkCount]
$cenumFromTo :: ShrinkCount -> ShrinkCount -> [ShrinkCount]
enumFromThen :: ShrinkCount -> ShrinkCount -> [ShrinkCount]
$cenumFromThen :: ShrinkCount -> ShrinkCount -> [ShrinkCount]
enumFrom :: ShrinkCount -> [ShrinkCount]
$cenumFrom :: ShrinkCount -> [ShrinkCount]
fromEnum :: ShrinkCount -> Int
$cfromEnum :: ShrinkCount -> Int
toEnum :: Int -> ShrinkCount
$ctoEnum :: Int -> ShrinkCount
pred :: ShrinkCount -> ShrinkCount
$cpred :: ShrinkCount -> ShrinkCount
succ :: ShrinkCount -> ShrinkCount
$csucc :: ShrinkCount -> ShrinkCount
Enum, Num ShrinkCount
Ord ShrinkCount
Num ShrinkCount
-> Ord ShrinkCount -> (ShrinkCount -> Rational) -> Real ShrinkCount
ShrinkCount -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: ShrinkCount -> Rational
$ctoRational :: ShrinkCount -> Rational
$cp2Real :: Ord ShrinkCount
$cp1Real :: Num ShrinkCount
Real, Enum ShrinkCount
Real ShrinkCount
Real ShrinkCount
-> Enum ShrinkCount
-> (ShrinkCount -> ShrinkCount -> ShrinkCount)
-> (ShrinkCount -> ShrinkCount -> ShrinkCount)
-> (ShrinkCount -> ShrinkCount -> ShrinkCount)
-> (ShrinkCount -> ShrinkCount -> ShrinkCount)
-> (ShrinkCount -> ShrinkCount -> (ShrinkCount, ShrinkCount))
-> (ShrinkCount -> ShrinkCount -> (ShrinkCount, ShrinkCount))
-> (ShrinkCount -> Integer)
-> Integral ShrinkCount
ShrinkCount -> Integer
ShrinkCount -> ShrinkCount -> (ShrinkCount, ShrinkCount)
ShrinkCount -> ShrinkCount -> ShrinkCount
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: ShrinkCount -> Integer
$ctoInteger :: ShrinkCount -> Integer
divMod :: ShrinkCount -> ShrinkCount -> (ShrinkCount, ShrinkCount)
$cdivMod :: ShrinkCount -> ShrinkCount -> (ShrinkCount, ShrinkCount)
quotRem :: ShrinkCount -> ShrinkCount -> (ShrinkCount, ShrinkCount)
$cquotRem :: ShrinkCount -> ShrinkCount -> (ShrinkCount, ShrinkCount)
mod :: ShrinkCount -> ShrinkCount -> ShrinkCount
$cmod :: ShrinkCount -> ShrinkCount -> ShrinkCount
div :: ShrinkCount -> ShrinkCount -> ShrinkCount
$cdiv :: ShrinkCount -> ShrinkCount -> ShrinkCount
rem :: ShrinkCount -> ShrinkCount -> ShrinkCount
$crem :: ShrinkCount -> ShrinkCount -> ShrinkCount
quot :: ShrinkCount -> ShrinkCount -> ShrinkCount
$cquot :: ShrinkCount -> ShrinkCount -> ShrinkCount
$cp2Integral :: Enum ShrinkCount
$cp1Integral :: Real ShrinkCount
Integral)

-- | The number of times to re-run a test during shrinking. This is useful if
--   you are testing something which fails non-deterministically and you want to
--   increase the change of getting a good shrink.
--
--   If you are doing parallel state machine testing, you should probably set
--   shrink retries to something like @10@. This will mean that during
--   shrinking, a parallel test case requires 10 successful runs before it is
--   passes and we try a different shrink.
--
--   Can be constructed using numeric literals:
--
-- @
--   0 :: ShrinkRetries
-- @
--
newtype ShrinkRetries =
  ShrinkRetries Int
  deriving (ShrinkRetries -> ShrinkRetries -> Bool
(ShrinkRetries -> ShrinkRetries -> Bool)
-> (ShrinkRetries -> ShrinkRetries -> Bool) -> Eq ShrinkRetries
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShrinkRetries -> ShrinkRetries -> Bool
$c/= :: ShrinkRetries -> ShrinkRetries -> Bool
== :: ShrinkRetries -> ShrinkRetries -> Bool
$c== :: ShrinkRetries -> ShrinkRetries -> Bool
Eq, Eq ShrinkRetries
Eq ShrinkRetries
-> (ShrinkRetries -> ShrinkRetries -> Ordering)
-> (ShrinkRetries -> ShrinkRetries -> Bool)
-> (ShrinkRetries -> ShrinkRetries -> Bool)
-> (ShrinkRetries -> ShrinkRetries -> Bool)
-> (ShrinkRetries -> ShrinkRetries -> Bool)
-> (ShrinkRetries -> ShrinkRetries -> ShrinkRetries)
-> (ShrinkRetries -> ShrinkRetries -> ShrinkRetries)
-> Ord ShrinkRetries
ShrinkRetries -> ShrinkRetries -> Bool
ShrinkRetries -> ShrinkRetries -> Ordering
ShrinkRetries -> ShrinkRetries -> ShrinkRetries
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
$cmin :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
max :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
$cmax :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
>= :: ShrinkRetries -> ShrinkRetries -> Bool
$c>= :: ShrinkRetries -> ShrinkRetries -> Bool
> :: ShrinkRetries -> ShrinkRetries -> Bool
$c> :: ShrinkRetries -> ShrinkRetries -> Bool
<= :: ShrinkRetries -> ShrinkRetries -> Bool
$c<= :: ShrinkRetries -> ShrinkRetries -> Bool
< :: ShrinkRetries -> ShrinkRetries -> Bool
$c< :: ShrinkRetries -> ShrinkRetries -> Bool
compare :: ShrinkRetries -> ShrinkRetries -> Ordering
$ccompare :: ShrinkRetries -> ShrinkRetries -> Ordering
$cp1Ord :: Eq ShrinkRetries
Ord, Int -> ShrinkRetries -> ShowS
[ShrinkRetries] -> ShowS
ShrinkRetries -> String
(Int -> ShrinkRetries -> ShowS)
-> (ShrinkRetries -> String)
-> ([ShrinkRetries] -> ShowS)
-> Show ShrinkRetries
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShrinkRetries] -> ShowS
$cshowList :: [ShrinkRetries] -> ShowS
show :: ShrinkRetries -> String
$cshow :: ShrinkRetries -> String
showsPrec :: Int -> ShrinkRetries -> ShowS
$cshowsPrec :: Int -> ShrinkRetries -> ShowS
Show, Integer -> ShrinkRetries
ShrinkRetries -> ShrinkRetries
ShrinkRetries -> ShrinkRetries -> ShrinkRetries
(ShrinkRetries -> ShrinkRetries -> ShrinkRetries)
-> (ShrinkRetries -> ShrinkRetries -> ShrinkRetries)
-> (ShrinkRetries -> ShrinkRetries -> ShrinkRetries)
-> (ShrinkRetries -> ShrinkRetries)
-> (ShrinkRetries -> ShrinkRetries)
-> (ShrinkRetries -> ShrinkRetries)
-> (Integer -> ShrinkRetries)
-> Num ShrinkRetries
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ShrinkRetries
$cfromInteger :: Integer -> ShrinkRetries
signum :: ShrinkRetries -> ShrinkRetries
$csignum :: ShrinkRetries -> ShrinkRetries
abs :: ShrinkRetries -> ShrinkRetries
$cabs :: ShrinkRetries -> ShrinkRetries
negate :: ShrinkRetries -> ShrinkRetries
$cnegate :: ShrinkRetries -> ShrinkRetries
* :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
$c* :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
- :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
$c- :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
+ :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
$c+ :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
Num, Int -> ShrinkRetries
ShrinkRetries -> Int
ShrinkRetries -> [ShrinkRetries]
ShrinkRetries -> ShrinkRetries
ShrinkRetries -> ShrinkRetries -> [ShrinkRetries]
ShrinkRetries -> ShrinkRetries -> ShrinkRetries -> [ShrinkRetries]
(ShrinkRetries -> ShrinkRetries)
-> (ShrinkRetries -> ShrinkRetries)
-> (Int -> ShrinkRetries)
-> (ShrinkRetries -> Int)
-> (ShrinkRetries -> [ShrinkRetries])
-> (ShrinkRetries -> ShrinkRetries -> [ShrinkRetries])
-> (ShrinkRetries -> ShrinkRetries -> [ShrinkRetries])
-> (ShrinkRetries
    -> ShrinkRetries -> ShrinkRetries -> [ShrinkRetries])
-> Enum ShrinkRetries
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries -> [ShrinkRetries]
$cenumFromThenTo :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries -> [ShrinkRetries]
enumFromTo :: ShrinkRetries -> ShrinkRetries -> [ShrinkRetries]
$cenumFromTo :: ShrinkRetries -> ShrinkRetries -> [ShrinkRetries]
enumFromThen :: ShrinkRetries -> ShrinkRetries -> [ShrinkRetries]
$cenumFromThen :: ShrinkRetries -> ShrinkRetries -> [ShrinkRetries]
enumFrom :: ShrinkRetries -> [ShrinkRetries]
$cenumFrom :: ShrinkRetries -> [ShrinkRetries]
fromEnum :: ShrinkRetries -> Int
$cfromEnum :: ShrinkRetries -> Int
toEnum :: Int -> ShrinkRetries
$ctoEnum :: Int -> ShrinkRetries
pred :: ShrinkRetries -> ShrinkRetries
$cpred :: ShrinkRetries -> ShrinkRetries
succ :: ShrinkRetries -> ShrinkRetries
$csucc :: ShrinkRetries -> ShrinkRetries
Enum, Num ShrinkRetries
Ord ShrinkRetries
Num ShrinkRetries
-> Ord ShrinkRetries
-> (ShrinkRetries -> Rational)
-> Real ShrinkRetries
ShrinkRetries -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: ShrinkRetries -> Rational
$ctoRational :: ShrinkRetries -> Rational
$cp2Real :: Ord ShrinkRetries
$cp1Real :: Num ShrinkRetries
Real, Enum ShrinkRetries
Real ShrinkRetries
Real ShrinkRetries
-> Enum ShrinkRetries
-> (ShrinkRetries -> ShrinkRetries -> ShrinkRetries)
-> (ShrinkRetries -> ShrinkRetries -> ShrinkRetries)
-> (ShrinkRetries -> ShrinkRetries -> ShrinkRetries)
-> (ShrinkRetries -> ShrinkRetries -> ShrinkRetries)
-> (ShrinkRetries
    -> ShrinkRetries -> (ShrinkRetries, ShrinkRetries))
-> (ShrinkRetries
    -> ShrinkRetries -> (ShrinkRetries, ShrinkRetries))
-> (ShrinkRetries -> Integer)
-> Integral ShrinkRetries
ShrinkRetries -> Integer
ShrinkRetries -> ShrinkRetries -> (ShrinkRetries, ShrinkRetries)
ShrinkRetries -> ShrinkRetries -> ShrinkRetries
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: ShrinkRetries -> Integer
$ctoInteger :: ShrinkRetries -> Integer
divMod :: ShrinkRetries -> ShrinkRetries -> (ShrinkRetries, ShrinkRetries)
$cdivMod :: ShrinkRetries -> ShrinkRetries -> (ShrinkRetries, ShrinkRetries)
quotRem :: ShrinkRetries -> ShrinkRetries -> (ShrinkRetries, ShrinkRetries)
$cquotRem :: ShrinkRetries -> ShrinkRetries -> (ShrinkRetries, ShrinkRetries)
mod :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
$cmod :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
div :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
$cdiv :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
rem :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
$crem :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
quot :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
$cquot :: ShrinkRetries -> ShrinkRetries -> ShrinkRetries
$cp2Integral :: Enum ShrinkRetries
$cp1Integral :: Real ShrinkRetries
Integral, ShrinkRetries -> Q Exp
ShrinkRetries -> Q (TExp ShrinkRetries)
(ShrinkRetries -> Q Exp)
-> (ShrinkRetries -> Q (TExp ShrinkRetries)) -> Lift ShrinkRetries
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: ShrinkRetries -> Q (TExp ShrinkRetries)
$cliftTyped :: ShrinkRetries -> Q (TExp ShrinkRetries)
lift :: ShrinkRetries -> Q Exp
$clift :: ShrinkRetries -> Q Exp
Lift)

-- | A named collection of property tests.
--
data Group =
  Group {
      Group -> GroupName
groupName :: !GroupName
    , Group -> [(PropertyName, Property)]
groupProperties :: ![(PropertyName, Property)]
    }

-- | The name of a group of properties.
--
--   Should be constructed using `OverloadedStrings`:
--
-- @
--   "fruit" :: GroupName
-- @
--
newtype GroupName =
  GroupName {
      GroupName -> String
unGroupName :: String
    } deriving (GroupName -> GroupName -> Bool
(GroupName -> GroupName -> Bool)
-> (GroupName -> GroupName -> Bool) -> Eq GroupName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GroupName -> GroupName -> Bool
$c/= :: GroupName -> GroupName -> Bool
== :: GroupName -> GroupName -> Bool
$c== :: GroupName -> GroupName -> Bool
Eq, Eq GroupName
Eq GroupName
-> (GroupName -> GroupName -> Ordering)
-> (GroupName -> GroupName -> Bool)
-> (GroupName -> GroupName -> Bool)
-> (GroupName -> GroupName -> Bool)
-> (GroupName -> GroupName -> Bool)
-> (GroupName -> GroupName -> GroupName)
-> (GroupName -> GroupName -> GroupName)
-> Ord GroupName
GroupName -> GroupName -> Bool
GroupName -> GroupName -> Ordering
GroupName -> GroupName -> GroupName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GroupName -> GroupName -> GroupName
$cmin :: GroupName -> GroupName -> GroupName
max :: GroupName -> GroupName -> GroupName
$cmax :: GroupName -> GroupName -> GroupName
>= :: GroupName -> GroupName -> Bool
$c>= :: GroupName -> GroupName -> Bool
> :: GroupName -> GroupName -> Bool
$c> :: GroupName -> GroupName -> Bool
<= :: GroupName -> GroupName -> Bool
$c<= :: GroupName -> GroupName -> Bool
< :: GroupName -> GroupName -> Bool
$c< :: GroupName -> GroupName -> Bool
compare :: GroupName -> GroupName -> Ordering
$ccompare :: GroupName -> GroupName -> Ordering
$cp1Ord :: Eq GroupName
Ord, Int -> GroupName -> ShowS
[GroupName] -> ShowS
GroupName -> String
(Int -> GroupName -> ShowS)
-> (GroupName -> String)
-> ([GroupName] -> ShowS)
-> Show GroupName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GroupName] -> ShowS
$cshowList :: [GroupName] -> ShowS
show :: GroupName -> String
$cshow :: GroupName -> String
showsPrec :: Int -> GroupName -> ShowS
$cshowsPrec :: Int -> GroupName -> ShowS
Show, String -> GroupName
(String -> GroupName) -> IsString GroupName
forall a. (String -> a) -> IsString a
fromString :: String -> GroupName
$cfromString :: String -> GroupName
IsString, b -> GroupName -> GroupName
NonEmpty GroupName -> GroupName
GroupName -> GroupName -> GroupName
(GroupName -> GroupName -> GroupName)
-> (NonEmpty GroupName -> GroupName)
-> (forall b. Integral b => b -> GroupName -> GroupName)
-> Semigroup GroupName
forall b. Integral b => b -> GroupName -> GroupName
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> GroupName -> GroupName
$cstimes :: forall b. Integral b => b -> GroupName -> GroupName
sconcat :: NonEmpty GroupName -> GroupName
$csconcat :: NonEmpty GroupName -> GroupName
<> :: GroupName -> GroupName -> GroupName
$c<> :: GroupName -> GroupName -> GroupName
Semigroup, GroupName -> Q Exp
GroupName -> Q (TExp GroupName)
(GroupName -> Q Exp)
-> (GroupName -> Q (TExp GroupName)) -> Lift GroupName
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: GroupName -> Q (TExp GroupName)
$cliftTyped :: GroupName -> Q (TExp GroupName)
lift :: GroupName -> Q Exp
$clift :: GroupName -> Q Exp
Lift)

-- | The number of properties in a group.
--
newtype PropertyCount =
  PropertyCount Int
  deriving (PropertyCount -> PropertyCount -> Bool
(PropertyCount -> PropertyCount -> Bool)
-> (PropertyCount -> PropertyCount -> Bool) -> Eq PropertyCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PropertyCount -> PropertyCount -> Bool
$c/= :: PropertyCount -> PropertyCount -> Bool
== :: PropertyCount -> PropertyCount -> Bool
$c== :: PropertyCount -> PropertyCount -> Bool
Eq, Eq PropertyCount
Eq PropertyCount
-> (PropertyCount -> PropertyCount -> Ordering)
-> (PropertyCount -> PropertyCount -> Bool)
-> (PropertyCount -> PropertyCount -> Bool)
-> (PropertyCount -> PropertyCount -> Bool)
-> (PropertyCount -> PropertyCount -> Bool)
-> (PropertyCount -> PropertyCount -> PropertyCount)
-> (PropertyCount -> PropertyCount -> PropertyCount)
-> Ord PropertyCount
PropertyCount -> PropertyCount -> Bool
PropertyCount -> PropertyCount -> Ordering
PropertyCount -> PropertyCount -> PropertyCount
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PropertyCount -> PropertyCount -> PropertyCount
$cmin :: PropertyCount -> PropertyCount -> PropertyCount
max :: PropertyCount -> PropertyCount -> PropertyCount
$cmax :: PropertyCount -> PropertyCount -> PropertyCount
>= :: PropertyCount -> PropertyCount -> Bool
$c>= :: PropertyCount -> PropertyCount -> Bool
> :: PropertyCount -> PropertyCount -> Bool
$c> :: PropertyCount -> PropertyCount -> Bool
<= :: PropertyCount -> PropertyCount -> Bool
$c<= :: PropertyCount -> PropertyCount -> Bool
< :: PropertyCount -> PropertyCount -> Bool
$c< :: PropertyCount -> PropertyCount -> Bool
compare :: PropertyCount -> PropertyCount -> Ordering
$ccompare :: PropertyCount -> PropertyCount -> Ordering
$cp1Ord :: Eq PropertyCount
Ord, Int -> PropertyCount -> ShowS
[PropertyCount] -> ShowS
PropertyCount -> String
(Int -> PropertyCount -> ShowS)
-> (PropertyCount -> String)
-> ([PropertyCount] -> ShowS)
-> Show PropertyCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PropertyCount] -> ShowS
$cshowList :: [PropertyCount] -> ShowS
show :: PropertyCount -> String
$cshow :: PropertyCount -> String
showsPrec :: Int -> PropertyCount -> ShowS
$cshowsPrec :: Int -> PropertyCount -> ShowS
Show, Integer -> PropertyCount
PropertyCount -> PropertyCount
PropertyCount -> PropertyCount -> PropertyCount
(PropertyCount -> PropertyCount -> PropertyCount)
-> (PropertyCount -> PropertyCount -> PropertyCount)
-> (PropertyCount -> PropertyCount -> PropertyCount)
-> (PropertyCount -> PropertyCount)
-> (PropertyCount -> PropertyCount)
-> (PropertyCount -> PropertyCount)
-> (Integer -> PropertyCount)
-> Num PropertyCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> PropertyCount
$cfromInteger :: Integer -> PropertyCount
signum :: PropertyCount -> PropertyCount
$csignum :: PropertyCount -> PropertyCount
abs :: PropertyCount -> PropertyCount
$cabs :: PropertyCount -> PropertyCount
negate :: PropertyCount -> PropertyCount
$cnegate :: PropertyCount -> PropertyCount
* :: PropertyCount -> PropertyCount -> PropertyCount
$c* :: PropertyCount -> PropertyCount -> PropertyCount
- :: PropertyCount -> PropertyCount -> PropertyCount
$c- :: PropertyCount -> PropertyCount -> PropertyCount
+ :: PropertyCount -> PropertyCount -> PropertyCount
$c+ :: PropertyCount -> PropertyCount -> PropertyCount
Num, Int -> PropertyCount
PropertyCount -> Int
PropertyCount -> [PropertyCount]
PropertyCount -> PropertyCount
PropertyCount -> PropertyCount -> [PropertyCount]
PropertyCount -> PropertyCount -> PropertyCount -> [PropertyCount]
(PropertyCount -> PropertyCount)
-> (PropertyCount -> PropertyCount)
-> (Int -> PropertyCount)
-> (PropertyCount -> Int)
-> (PropertyCount -> [PropertyCount])
-> (PropertyCount -> PropertyCount -> [PropertyCount])
-> (PropertyCount -> PropertyCount -> [PropertyCount])
-> (PropertyCount
    -> PropertyCount -> PropertyCount -> [PropertyCount])
-> Enum PropertyCount
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: PropertyCount -> PropertyCount -> PropertyCount -> [PropertyCount]
$cenumFromThenTo :: PropertyCount -> PropertyCount -> PropertyCount -> [PropertyCount]
enumFromTo :: PropertyCount -> PropertyCount -> [PropertyCount]
$cenumFromTo :: PropertyCount -> PropertyCount -> [PropertyCount]
enumFromThen :: PropertyCount -> PropertyCount -> [PropertyCount]
$cenumFromThen :: PropertyCount -> PropertyCount -> [PropertyCount]
enumFrom :: PropertyCount -> [PropertyCount]
$cenumFrom :: PropertyCount -> [PropertyCount]
fromEnum :: PropertyCount -> Int
$cfromEnum :: PropertyCount -> Int
toEnum :: Int -> PropertyCount
$ctoEnum :: Int -> PropertyCount
pred :: PropertyCount -> PropertyCount
$cpred :: PropertyCount -> PropertyCount
succ :: PropertyCount -> PropertyCount
$csucc :: PropertyCount -> PropertyCount
Enum, Num PropertyCount
Ord PropertyCount
Num PropertyCount
-> Ord PropertyCount
-> (PropertyCount -> Rational)
-> Real PropertyCount
PropertyCount -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: PropertyCount -> Rational
$ctoRational :: PropertyCount -> Rational
$cp2Real :: Ord PropertyCount
$cp1Real :: Num PropertyCount
Real, Enum PropertyCount
Real PropertyCount
Real PropertyCount
-> Enum PropertyCount
-> (PropertyCount -> PropertyCount -> PropertyCount)
-> (PropertyCount -> PropertyCount -> PropertyCount)
-> (PropertyCount -> PropertyCount -> PropertyCount)
-> (PropertyCount -> PropertyCount -> PropertyCount)
-> (PropertyCount
    -> PropertyCount -> (PropertyCount, PropertyCount))
-> (PropertyCount
    -> PropertyCount -> (PropertyCount, PropertyCount))
-> (PropertyCount -> Integer)
-> Integral PropertyCount
PropertyCount -> Integer
PropertyCount -> PropertyCount -> (PropertyCount, PropertyCount)
PropertyCount -> PropertyCount -> PropertyCount
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: PropertyCount -> Integer
$ctoInteger :: PropertyCount -> Integer
divMod :: PropertyCount -> PropertyCount -> (PropertyCount, PropertyCount)
$cdivMod :: PropertyCount -> PropertyCount -> (PropertyCount, PropertyCount)
quotRem :: PropertyCount -> PropertyCount -> (PropertyCount, PropertyCount)
$cquotRem :: PropertyCount -> PropertyCount -> (PropertyCount, PropertyCount)
mod :: PropertyCount -> PropertyCount -> PropertyCount
$cmod :: PropertyCount -> PropertyCount -> PropertyCount
div :: PropertyCount -> PropertyCount -> PropertyCount
$cdiv :: PropertyCount -> PropertyCount -> PropertyCount
rem :: PropertyCount -> PropertyCount -> PropertyCount
$crem :: PropertyCount -> PropertyCount -> PropertyCount
quot :: PropertyCount -> PropertyCount -> PropertyCount
$cquot :: PropertyCount -> PropertyCount -> PropertyCount
$cp2Integral :: Enum PropertyCount
$cp1Integral :: Real PropertyCount
Integral)

data TerminationCriteria =
    EarlyTermination Confidence TestLimit
  | NoEarlyTermination Confidence TestLimit
  | NoConfidenceTermination TestLimit
  deriving (TerminationCriteria -> TerminationCriteria -> Bool
(TerminationCriteria -> TerminationCriteria -> Bool)
-> (TerminationCriteria -> TerminationCriteria -> Bool)
-> Eq TerminationCriteria
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TerminationCriteria -> TerminationCriteria -> Bool
$c/= :: TerminationCriteria -> TerminationCriteria -> Bool
== :: TerminationCriteria -> TerminationCriteria -> Bool
$c== :: TerminationCriteria -> TerminationCriteria -> Bool
Eq, Eq TerminationCriteria
Eq TerminationCriteria
-> (TerminationCriteria -> TerminationCriteria -> Ordering)
-> (TerminationCriteria -> TerminationCriteria -> Bool)
-> (TerminationCriteria -> TerminationCriteria -> Bool)
-> (TerminationCriteria -> TerminationCriteria -> Bool)
-> (TerminationCriteria -> TerminationCriteria -> Bool)
-> (TerminationCriteria
    -> TerminationCriteria -> TerminationCriteria)
-> (TerminationCriteria
    -> TerminationCriteria -> TerminationCriteria)
-> Ord TerminationCriteria
TerminationCriteria -> TerminationCriteria -> Bool
TerminationCriteria -> TerminationCriteria -> Ordering
TerminationCriteria -> TerminationCriteria -> TerminationCriteria
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TerminationCriteria -> TerminationCriteria -> TerminationCriteria
$cmin :: TerminationCriteria -> TerminationCriteria -> TerminationCriteria
max :: TerminationCriteria -> TerminationCriteria -> TerminationCriteria
$cmax :: TerminationCriteria -> TerminationCriteria -> TerminationCriteria
>= :: TerminationCriteria -> TerminationCriteria -> Bool
$c>= :: TerminationCriteria -> TerminationCriteria -> Bool
> :: TerminationCriteria -> TerminationCriteria -> Bool
$c> :: TerminationCriteria -> TerminationCriteria -> Bool
<= :: TerminationCriteria -> TerminationCriteria -> Bool
$c<= :: TerminationCriteria -> TerminationCriteria -> Bool
< :: TerminationCriteria -> TerminationCriteria -> Bool
$c< :: TerminationCriteria -> TerminationCriteria -> Bool
compare :: TerminationCriteria -> TerminationCriteria -> Ordering
$ccompare :: TerminationCriteria -> TerminationCriteria -> Ordering
$cp1Ord :: Eq TerminationCriteria
Ord, Int -> TerminationCriteria -> ShowS
[TerminationCriteria] -> ShowS
TerminationCriteria -> String
(Int -> TerminationCriteria -> ShowS)
-> (TerminationCriteria -> String)
-> ([TerminationCriteria] -> ShowS)
-> Show TerminationCriteria
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TerminationCriteria] -> ShowS
$cshowList :: [TerminationCriteria] -> ShowS
show :: TerminationCriteria -> String
$cshow :: TerminationCriteria -> String
showsPrec :: Int -> TerminationCriteria -> ShowS
$cshowsPrec :: Int -> TerminationCriteria -> ShowS
Show, TerminationCriteria -> Q Exp
TerminationCriteria -> Q (TExp TerminationCriteria)
(TerminationCriteria -> Q Exp)
-> (TerminationCriteria -> Q (TExp TerminationCriteria))
-> Lift TerminationCriteria
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: TerminationCriteria -> Q (TExp TerminationCriteria)
$cliftTyped :: TerminationCriteria -> Q (TExp TerminationCriteria)
lift :: TerminationCriteria -> Q Exp
$clift :: TerminationCriteria -> Q Exp
Lift)

--
-- FIXME This whole Log/Failure thing could be a lot more structured to allow
-- FIXME for richer user controlled error messages, think Doc. Ideally we'd
-- FIXME allow user's to crete their own diffs anywhere.
--

-- | Log messages which are recorded during a test run.
--
data Log =
    Annotation (Maybe Span) String
  | Footnote String
  | Label (Label Cover)
    deriving (Log -> Log -> Bool
(Log -> Log -> Bool) -> (Log -> Log -> Bool) -> Eq Log
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Log -> Log -> Bool
$c/= :: Log -> Log -> Bool
== :: Log -> Log -> Bool
$c== :: Log -> Log -> Bool
Eq, Int -> Log -> ShowS
[Log] -> ShowS
Log -> String
(Int -> Log -> ShowS)
-> (Log -> String) -> ([Log] -> ShowS) -> Show Log
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Log] -> ShowS
$cshowList :: [Log] -> ShowS
show :: Log -> String
$cshow :: Log -> String
showsPrec :: Int -> Log -> ShowS
$cshowsPrec :: Int -> Log -> ShowS
Show)

-- | A record containing the details of a test run.
newtype Journal =
  Journal {
      Journal -> [Log]
journalLogs :: [Log]
    } deriving (Journal -> Journal -> Bool
(Journal -> Journal -> Bool)
-> (Journal -> Journal -> Bool) -> Eq Journal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Journal -> Journal -> Bool
$c/= :: Journal -> Journal -> Bool
== :: Journal -> Journal -> Bool
$c== :: Journal -> Journal -> Bool
Eq, Int -> Journal -> ShowS
[Journal] -> ShowS
Journal -> String
(Int -> Journal -> ShowS)
-> (Journal -> String) -> ([Journal] -> ShowS) -> Show Journal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Journal] -> ShowS
$cshowList :: [Journal] -> ShowS
show :: Journal -> String
$cshow :: Journal -> String
showsPrec :: Int -> Journal -> ShowS
$cshowsPrec :: Int -> Journal -> ShowS
Show, b -> Journal -> Journal
NonEmpty Journal -> Journal
Journal -> Journal -> Journal
(Journal -> Journal -> Journal)
-> (NonEmpty Journal -> Journal)
-> (forall b. Integral b => b -> Journal -> Journal)
-> Semigroup Journal
forall b. Integral b => b -> Journal -> Journal
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> Journal -> Journal
$cstimes :: forall b. Integral b => b -> Journal -> Journal
sconcat :: NonEmpty Journal -> Journal
$csconcat :: NonEmpty Journal -> Journal
<> :: Journal -> Journal -> Journal
$c<> :: Journal -> Journal -> Journal
Semigroup, Semigroup Journal
Journal
Semigroup Journal
-> Journal
-> (Journal -> Journal -> Journal)
-> ([Journal] -> Journal)
-> Monoid Journal
[Journal] -> Journal
Journal -> Journal -> Journal
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [Journal] -> Journal
$cmconcat :: [Journal] -> Journal
mappend :: Journal -> Journal -> Journal
$cmappend :: Journal -> Journal -> Journal
mempty :: Journal
$cmempty :: Journal
$cp1Monoid :: Semigroup Journal
Monoid)

-- | Details on where and why a test failed.
--
data Failure =
  Failure (Maybe Span) String (Maybe Diff)
  deriving (Failure -> Failure -> Bool
(Failure -> Failure -> Bool)
-> (Failure -> Failure -> Bool) -> Eq Failure
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Failure -> Failure -> Bool
$c/= :: Failure -> Failure -> Bool
== :: Failure -> Failure -> Bool
$c== :: Failure -> Failure -> Bool
Eq, Int -> Failure -> ShowS
[Failure] -> ShowS
Failure -> String
(Int -> Failure -> ShowS)
-> (Failure -> String) -> ([Failure] -> ShowS) -> Show Failure
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Failure] -> ShowS
$cshowList :: [Failure] -> ShowS
show :: Failure -> String
$cshow :: Failure -> String
showsPrec :: Int -> Failure -> ShowS
$cshowsPrec :: Int -> Failure -> ShowS
Show)

-- | The difference between some expected and actual value.
--
data Diff =
  Diff {
      Diff -> String
diffPrefix :: String
    , Diff -> String
diffRemoved :: String
    , Diff -> String
diffInfix :: String
    , Diff -> String
diffAdded :: String
    , Diff -> String
diffSuffix :: String
    , Diff -> ValueDiff
diffValue :: ValueDiff
    } deriving (Diff -> Diff -> Bool
(Diff -> Diff -> Bool) -> (Diff -> Diff -> Bool) -> Eq Diff
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Diff -> Diff -> Bool
$c/= :: Diff -> Diff -> Bool
== :: Diff -> Diff -> Bool
$c== :: Diff -> Diff -> Bool
Eq, Int -> Diff -> ShowS
[Diff] -> ShowS
Diff -> String
(Int -> Diff -> ShowS)
-> (Diff -> String) -> ([Diff] -> ShowS) -> Show Diff
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Diff] -> ShowS
$cshowList :: [Diff] -> ShowS
show :: Diff -> String
$cshow :: Diff -> String
showsPrec :: Int -> Diff -> ShowS
$cshowsPrec :: Int -> Diff -> ShowS
Show)

-- | Whether a test is covered by a classifier, and therefore belongs to a
--   'Class'.
--
data Cover =
    NoCover
  | Cover
    deriving (Cover -> Cover -> Bool
(Cover -> Cover -> Bool) -> (Cover -> Cover -> Bool) -> Eq Cover
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cover -> Cover -> Bool
$c/= :: Cover -> Cover -> Bool
== :: Cover -> Cover -> Bool
$c== :: Cover -> Cover -> Bool
Eq, Eq Cover
Eq Cover
-> (Cover -> Cover -> Ordering)
-> (Cover -> Cover -> Bool)
-> (Cover -> Cover -> Bool)
-> (Cover -> Cover -> Bool)
-> (Cover -> Cover -> Bool)
-> (Cover -> Cover -> Cover)
-> (Cover -> Cover -> Cover)
-> Ord Cover
Cover -> Cover -> Bool
Cover -> Cover -> Ordering
Cover -> Cover -> Cover
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Cover -> Cover -> Cover
$cmin :: Cover -> Cover -> Cover
max :: Cover -> Cover -> Cover
$cmax :: Cover -> Cover -> Cover
>= :: Cover -> Cover -> Bool
$c>= :: Cover -> Cover -> Bool
> :: Cover -> Cover -> Bool
$c> :: Cover -> Cover -> Bool
<= :: Cover -> Cover -> Bool
$c<= :: Cover -> Cover -> Bool
< :: Cover -> Cover -> Bool
$c< :: Cover -> Cover -> Bool
compare :: Cover -> Cover -> Ordering
$ccompare :: Cover -> Cover -> Ordering
$cp1Ord :: Eq Cover
Ord, Int -> Cover -> ShowS
[Cover] -> ShowS
Cover -> String
(Int -> Cover -> ShowS)
-> (Cover -> String) -> ([Cover] -> ShowS) -> Show Cover
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cover] -> ShowS
$cshowList :: [Cover] -> ShowS
show :: Cover -> String
$cshow :: Cover -> String
showsPrec :: Int -> Cover -> ShowS
$cshowsPrec :: Int -> Cover -> ShowS
Show)

-- | The total number of tests which are covered by a classifier.
--
--   Can be constructed using numeric literals:
--
-- @
--   30 :: CoverCount
-- @
--
newtype CoverCount =
  CoverCount {
      CoverCount -> Int
unCoverCount :: Int
    } deriving (CoverCount -> CoverCount -> Bool
(CoverCount -> CoverCount -> Bool)
-> (CoverCount -> CoverCount -> Bool) -> Eq CoverCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CoverCount -> CoverCount -> Bool
$c/= :: CoverCount -> CoverCount -> Bool
== :: CoverCount -> CoverCount -> Bool
$c== :: CoverCount -> CoverCount -> Bool
Eq, Eq CoverCount
Eq CoverCount
-> (CoverCount -> CoverCount -> Ordering)
-> (CoverCount -> CoverCount -> Bool)
-> (CoverCount -> CoverCount -> Bool)
-> (CoverCount -> CoverCount -> Bool)
-> (CoverCount -> CoverCount -> Bool)
-> (CoverCount -> CoverCount -> CoverCount)
-> (CoverCount -> CoverCount -> CoverCount)
-> Ord CoverCount
CoverCount -> CoverCount -> Bool
CoverCount -> CoverCount -> Ordering
CoverCount -> CoverCount -> CoverCount
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CoverCount -> CoverCount -> CoverCount
$cmin :: CoverCount -> CoverCount -> CoverCount
max :: CoverCount -> CoverCount -> CoverCount
$cmax :: CoverCount -> CoverCount -> CoverCount
>= :: CoverCount -> CoverCount -> Bool
$c>= :: CoverCount -> CoverCount -> Bool
> :: CoverCount -> CoverCount -> Bool
$c> :: CoverCount -> CoverCount -> Bool
<= :: CoverCount -> CoverCount -> Bool
$c<= :: CoverCount -> CoverCount -> Bool
< :: CoverCount -> CoverCount -> Bool
$c< :: CoverCount -> CoverCount -> Bool
compare :: CoverCount -> CoverCount -> Ordering
$ccompare :: CoverCount -> CoverCount -> Ordering
$cp1Ord :: Eq CoverCount
Ord, Int -> CoverCount -> ShowS
[CoverCount] -> ShowS
CoverCount -> String
(Int -> CoverCount -> ShowS)
-> (CoverCount -> String)
-> ([CoverCount] -> ShowS)
-> Show CoverCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CoverCount] -> ShowS
$cshowList :: [CoverCount] -> ShowS
show :: CoverCount -> String
$cshow :: CoverCount -> String
showsPrec :: Int -> CoverCount -> ShowS
$cshowsPrec :: Int -> CoverCount -> ShowS
Show, Integer -> CoverCount
CoverCount -> CoverCount
CoverCount -> CoverCount -> CoverCount
(CoverCount -> CoverCount -> CoverCount)
-> (CoverCount -> CoverCount -> CoverCount)
-> (CoverCount -> CoverCount -> CoverCount)
-> (CoverCount -> CoverCount)
-> (CoverCount -> CoverCount)
-> (CoverCount -> CoverCount)
-> (Integer -> CoverCount)
-> Num CoverCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> CoverCount
$cfromInteger :: Integer -> CoverCount
signum :: CoverCount -> CoverCount
$csignum :: CoverCount -> CoverCount
abs :: CoverCount -> CoverCount
$cabs :: CoverCount -> CoverCount
negate :: CoverCount -> CoverCount
$cnegate :: CoverCount -> CoverCount
* :: CoverCount -> CoverCount -> CoverCount
$c* :: CoverCount -> CoverCount -> CoverCount
- :: CoverCount -> CoverCount -> CoverCount
$c- :: CoverCount -> CoverCount -> CoverCount
+ :: CoverCount -> CoverCount -> CoverCount
$c+ :: CoverCount -> CoverCount -> CoverCount
Num)

-- | The relative number of tests which are covered by a classifier.
--
--   Can be constructed using numeric literals:
--
-- @
--   30 :: CoverPercentage
-- @
--
newtype CoverPercentage =
  CoverPercentage {
      CoverPercentage -> Double
unCoverPercentage :: Double
    } deriving (CoverPercentage -> CoverPercentage -> Bool
(CoverPercentage -> CoverPercentage -> Bool)
-> (CoverPercentage -> CoverPercentage -> Bool)
-> Eq CoverPercentage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CoverPercentage -> CoverPercentage -> Bool
$c/= :: CoverPercentage -> CoverPercentage -> Bool
== :: CoverPercentage -> CoverPercentage -> Bool
$c== :: CoverPercentage -> CoverPercentage -> Bool
Eq, Eq CoverPercentage
Eq CoverPercentage
-> (CoverPercentage -> CoverPercentage -> Ordering)
-> (CoverPercentage -> CoverPercentage -> Bool)
-> (CoverPercentage -> CoverPercentage -> Bool)
-> (CoverPercentage -> CoverPercentage -> Bool)
-> (CoverPercentage -> CoverPercentage -> Bool)
-> (CoverPercentage -> CoverPercentage -> CoverPercentage)
-> (CoverPercentage -> CoverPercentage -> CoverPercentage)
-> Ord CoverPercentage
CoverPercentage -> CoverPercentage -> Bool
CoverPercentage -> CoverPercentage -> Ordering
CoverPercentage -> CoverPercentage -> CoverPercentage
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CoverPercentage -> CoverPercentage -> CoverPercentage
$cmin :: CoverPercentage -> CoverPercentage -> CoverPercentage
max :: CoverPercentage -> CoverPercentage -> CoverPercentage
$cmax :: CoverPercentage -> CoverPercentage -> CoverPercentage
>= :: CoverPercentage -> CoverPercentage -> Bool
$c>= :: CoverPercentage -> CoverPercentage -> Bool
> :: CoverPercentage -> CoverPercentage -> Bool
$c> :: CoverPercentage -> CoverPercentage -> Bool
<= :: CoverPercentage -> CoverPercentage -> Bool
$c<= :: CoverPercentage -> CoverPercentage -> Bool
< :: CoverPercentage -> CoverPercentage -> Bool
$c< :: CoverPercentage -> CoverPercentage -> Bool
compare :: CoverPercentage -> CoverPercentage -> Ordering
$ccompare :: CoverPercentage -> CoverPercentage -> Ordering
$cp1Ord :: Eq CoverPercentage
Ord, Int -> CoverPercentage -> ShowS
[CoverPercentage] -> ShowS
CoverPercentage -> String
(Int -> CoverPercentage -> ShowS)
-> (CoverPercentage -> String)
-> ([CoverPercentage] -> ShowS)
-> Show CoverPercentage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CoverPercentage] -> ShowS
$cshowList :: [CoverPercentage] -> ShowS
show :: CoverPercentage -> String
$cshow :: CoverPercentage -> String
showsPrec :: Int -> CoverPercentage -> ShowS
$cshowsPrec :: Int -> CoverPercentage -> ShowS
Show, Integer -> CoverPercentage
CoverPercentage -> CoverPercentage
CoverPercentage -> CoverPercentage -> CoverPercentage
(CoverPercentage -> CoverPercentage -> CoverPercentage)
-> (CoverPercentage -> CoverPercentage -> CoverPercentage)
-> (CoverPercentage -> CoverPercentage -> CoverPercentage)
-> (CoverPercentage -> CoverPercentage)
-> (CoverPercentage -> CoverPercentage)
-> (CoverPercentage -> CoverPercentage)
-> (Integer -> CoverPercentage)
-> Num CoverPercentage
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> CoverPercentage
$cfromInteger :: Integer -> CoverPercentage
signum :: CoverPercentage -> CoverPercentage
$csignum :: CoverPercentage -> CoverPercentage
abs :: CoverPercentage -> CoverPercentage
$cabs :: CoverPercentage -> CoverPercentage
negate :: CoverPercentage -> CoverPercentage
$cnegate :: CoverPercentage -> CoverPercentage
* :: CoverPercentage -> CoverPercentage -> CoverPercentage
$c* :: CoverPercentage -> CoverPercentage -> CoverPercentage
- :: CoverPercentage -> CoverPercentage -> CoverPercentage
$c- :: CoverPercentage -> CoverPercentage -> CoverPercentage
+ :: CoverPercentage -> CoverPercentage -> CoverPercentage
$c+ :: CoverPercentage -> CoverPercentage -> CoverPercentage
Num, Num CoverPercentage
Num CoverPercentage
-> (CoverPercentage -> CoverPercentage -> CoverPercentage)
-> (CoverPercentage -> CoverPercentage)
-> (Rational -> CoverPercentage)
-> Fractional CoverPercentage
Rational -> CoverPercentage
CoverPercentage -> CoverPercentage
CoverPercentage -> CoverPercentage -> CoverPercentage
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
fromRational :: Rational -> CoverPercentage
$cfromRational :: Rational -> CoverPercentage
recip :: CoverPercentage -> CoverPercentage
$crecip :: CoverPercentage -> CoverPercentage
/ :: CoverPercentage -> CoverPercentage -> CoverPercentage
$c/ :: CoverPercentage -> CoverPercentage -> CoverPercentage
$cp1Fractional :: Num CoverPercentage
Fractional)

-- | The name of a classifier.
--
--   Should be constructed using `OverloadedStrings`:
--
-- @
--   "apples" :: LabelName
-- @
--
newtype LabelName =
  LabelName {
      LabelName -> String
unLabelName :: String
    } deriving (LabelName -> LabelName -> Bool
(LabelName -> LabelName -> Bool)
-> (LabelName -> LabelName -> Bool) -> Eq LabelName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LabelName -> LabelName -> Bool
$c/= :: LabelName -> LabelName -> Bool
== :: LabelName -> LabelName -> Bool
$c== :: LabelName -> LabelName -> Bool
Eq, Semigroup LabelName
LabelName
Semigroup LabelName
-> LabelName
-> (LabelName -> LabelName -> LabelName)
-> ([LabelName] -> LabelName)
-> Monoid LabelName
[LabelName] -> LabelName
LabelName -> LabelName -> LabelName
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [LabelName] -> LabelName
$cmconcat :: [LabelName] -> LabelName
mappend :: LabelName -> LabelName -> LabelName
$cmappend :: LabelName -> LabelName -> LabelName
mempty :: LabelName
$cmempty :: LabelName
$cp1Monoid :: Semigroup LabelName
Monoid, Eq LabelName
Eq LabelName
-> (LabelName -> LabelName -> Ordering)
-> (LabelName -> LabelName -> Bool)
-> (LabelName -> LabelName -> Bool)
-> (LabelName -> LabelName -> Bool)
-> (LabelName -> LabelName -> Bool)
-> (LabelName -> LabelName -> LabelName)
-> (LabelName -> LabelName -> LabelName)
-> Ord LabelName
LabelName -> LabelName -> Bool
LabelName -> LabelName -> Ordering
LabelName -> LabelName -> LabelName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LabelName -> LabelName -> LabelName
$cmin :: LabelName -> LabelName -> LabelName
max :: LabelName -> LabelName -> LabelName
$cmax :: LabelName -> LabelName -> LabelName
>= :: LabelName -> LabelName -> Bool
$c>= :: LabelName -> LabelName -> Bool
> :: LabelName -> LabelName -> Bool
$c> :: LabelName -> LabelName -> Bool
<= :: LabelName -> LabelName -> Bool
$c<= :: LabelName -> LabelName -> Bool
< :: LabelName -> LabelName -> Bool
$c< :: LabelName -> LabelName -> Bool
compare :: LabelName -> LabelName -> Ordering
$ccompare :: LabelName -> LabelName -> Ordering
$cp1Ord :: Eq LabelName
Ord, b -> LabelName -> LabelName
NonEmpty LabelName -> LabelName
LabelName -> LabelName -> LabelName
(LabelName -> LabelName -> LabelName)
-> (NonEmpty LabelName -> LabelName)
-> (forall b. Integral b => b -> LabelName -> LabelName)
-> Semigroup LabelName
forall b. Integral b => b -> LabelName -> LabelName
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> LabelName -> LabelName
$cstimes :: forall b. Integral b => b -> LabelName -> LabelName
sconcat :: NonEmpty LabelName -> LabelName
$csconcat :: NonEmpty LabelName -> LabelName
<> :: LabelName -> LabelName -> LabelName
$c<> :: LabelName -> LabelName -> LabelName
Semigroup, Int -> LabelName -> ShowS
[LabelName] -> ShowS
LabelName -> String
(Int -> LabelName -> ShowS)
-> (LabelName -> String)
-> ([LabelName] -> ShowS)
-> Show LabelName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LabelName] -> ShowS
$cshowList :: [LabelName] -> ShowS
show :: LabelName -> String
$cshow :: LabelName -> String
showsPrec :: Int -> LabelName -> ShowS
$cshowsPrec :: Int -> LabelName -> ShowS
Show, String -> LabelName
(String -> LabelName) -> IsString LabelName
forall a. (String -> a) -> IsString a
fromString :: String -> LabelName
$cfromString :: String -> LabelName
IsString)

-- | The extent to which a test is covered by a classifier.
--
--   /When a classifier's coverage does not exceed the required minimum, the/
--   /test will be failed./
--
data Label a =
  MkLabel {
      Label a -> LabelName
labelName :: !LabelName
    , Label a -> Maybe Span
labelLocation :: !(Maybe Span)
    , Label a -> CoverPercentage
labelMinimum :: !CoverPercentage
    , Label a -> a
labelAnnotation :: !a
    } deriving (Label a -> Label a -> Bool
(Label a -> Label a -> Bool)
-> (Label a -> Label a -> Bool) -> Eq (Label a)
forall a. Eq a => Label a -> Label a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Label a -> Label a -> Bool
$c/= :: forall a. Eq a => Label a -> Label a -> Bool
== :: Label a -> Label a -> Bool
$c== :: forall a. Eq a => Label a -> Label a -> Bool
Eq, Int -> Label a -> ShowS
[Label a] -> ShowS
Label a -> String
(Int -> Label a -> ShowS)
-> (Label a -> String) -> ([Label a] -> ShowS) -> Show (Label a)
forall a. Show a => Int -> Label a -> ShowS
forall a. Show a => [Label a] -> ShowS
forall a. Show a => Label a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Label a] -> ShowS
$cshowList :: forall a. Show a => [Label a] -> ShowS
show :: Label a -> String
$cshow :: forall a. Show a => Label a -> String
showsPrec :: Int -> Label a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Label a -> ShowS
Show, a -> Label b -> Label a
(a -> b) -> Label a -> Label b
(forall a b. (a -> b) -> Label a -> Label b)
-> (forall a b. a -> Label b -> Label a) -> Functor Label
forall a b. a -> Label b -> Label a
forall a b. (a -> b) -> Label a -> Label b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Label b -> Label a
$c<$ :: forall a b. a -> Label b -> Label a
fmap :: (a -> b) -> Label a -> Label b
$cfmap :: forall a b. (a -> b) -> Label a -> Label b
Functor, Label a -> Bool
(a -> m) -> Label a -> m
(a -> b -> b) -> b -> Label a -> b
(forall m. Monoid m => Label m -> m)
-> (forall m a. Monoid m => (a -> m) -> Label a -> m)
-> (forall m a. Monoid m => (a -> m) -> Label a -> m)
-> (forall a b. (a -> b -> b) -> b -> Label a -> b)
-> (forall a b. (a -> b -> b) -> b -> Label a -> b)
-> (forall b a. (b -> a -> b) -> b -> Label a -> b)
-> (forall b a. (b -> a -> b) -> b -> Label a -> b)
-> (forall a. (a -> a -> a) -> Label a -> a)
-> (forall a. (a -> a -> a) -> Label a -> a)
-> (forall a. Label a -> [a])
-> (forall a. Label a -> Bool)
-> (forall a. Label a -> Int)
-> (forall a. Eq a => a -> Label a -> Bool)
-> (forall a. Ord a => Label a -> a)
-> (forall a. Ord a => Label a -> a)
-> (forall a. Num a => Label a -> a)
-> (forall a. Num a => Label a -> a)
-> Foldable Label
forall a. Eq a => a -> Label a -> Bool
forall a. Num a => Label a -> a
forall a. Ord a => Label a -> a
forall m. Monoid m => Label m -> m
forall a. Label a -> Bool
forall a. Label a -> Int
forall a. Label a -> [a]
forall a. (a -> a -> a) -> Label a -> a
forall m a. Monoid m => (a -> m) -> Label a -> m
forall b a. (b -> a -> b) -> b -> Label a -> b
forall a b. (a -> b -> b) -> b -> Label a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Label a -> a
$cproduct :: forall a. Num a => Label a -> a
sum :: Label a -> a
$csum :: forall a. Num a => Label a -> a
minimum :: Label a -> a
$cminimum :: forall a. Ord a => Label a -> a
maximum :: Label a -> a
$cmaximum :: forall a. Ord a => Label a -> a
elem :: a -> Label a -> Bool
$celem :: forall a. Eq a => a -> Label a -> Bool
length :: Label a -> Int
$clength :: forall a. Label a -> Int
null :: Label a -> Bool
$cnull :: forall a. Label a -> Bool
toList :: Label a -> [a]
$ctoList :: forall a. Label a -> [a]
foldl1 :: (a -> a -> a) -> Label a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Label a -> a
foldr1 :: (a -> a -> a) -> Label a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Label a -> a
foldl' :: (b -> a -> b) -> b -> Label a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Label a -> b
foldl :: (b -> a -> b) -> b -> Label a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Label a -> b
foldr' :: (a -> b -> b) -> b -> Label a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Label a -> b
foldr :: (a -> b -> b) -> b -> Label a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Label a -> b
foldMap' :: (a -> m) -> Label a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Label a -> m
foldMap :: (a -> m) -> Label a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Label a -> m
fold :: Label m -> m
$cfold :: forall m. Monoid m => Label m -> m
Foldable, Functor Label
Foldable Label
Functor Label
-> Foldable Label
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Label a -> f (Label b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Label (f a) -> f (Label a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Label a -> m (Label b))
-> (forall (m :: * -> *) a. Monad m => Label (m a) -> m (Label a))
-> Traversable Label
(a -> f b) -> Label a -> f (Label b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Label (m a) -> m (Label a)
forall (f :: * -> *) a. Applicative f => Label (f a) -> f (Label a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Label a -> m (Label b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Label a -> f (Label b)
sequence :: Label (m a) -> m (Label a)
$csequence :: forall (m :: * -> *) a. Monad m => Label (m a) -> m (Label a)
mapM :: (a -> m b) -> Label a -> m (Label b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Label a -> m (Label b)
sequenceA :: Label (f a) -> f (Label a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Label (f a) -> f (Label a)
traverse :: (a -> f b) -> Label a -> f (Label b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Label a -> f (Label b)
$cp2Traversable :: Foldable Label
$cp1Traversable :: Functor Label
Traversable)

-- | The extent to which all classifiers cover a test.
--
--   /When a given classification's coverage does not exceed the required/
--   /minimum, the test will be failed./
--
newtype Coverage a =
  Coverage {
      Coverage a -> Map LabelName (Label a)
coverageLabels :: Map LabelName (Label a)
    } deriving (Coverage a -> Coverage a -> Bool
(Coverage a -> Coverage a -> Bool)
-> (Coverage a -> Coverage a -> Bool) -> Eq (Coverage a)
forall a. Eq a => Coverage a -> Coverage a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Coverage a -> Coverage a -> Bool
$c/= :: forall a. Eq a => Coverage a -> Coverage a -> Bool
== :: Coverage a -> Coverage a -> Bool
$c== :: forall a. Eq a => Coverage a -> Coverage a -> Bool
Eq, Int -> Coverage a -> ShowS
[Coverage a] -> ShowS
Coverage a -> String
(Int -> Coverage a -> ShowS)
-> (Coverage a -> String)
-> ([Coverage a] -> ShowS)
-> Show (Coverage a)
forall a. Show a => Int -> Coverage a -> ShowS
forall a. Show a => [Coverage a] -> ShowS
forall a. Show a => Coverage a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Coverage a] -> ShowS
$cshowList :: forall a. Show a => [Coverage a] -> ShowS
show :: Coverage a -> String
$cshow :: forall a. Show a => Coverage a -> String
showsPrec :: Int -> Coverage a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Coverage a -> ShowS
Show, a -> Coverage b -> Coverage a
(a -> b) -> Coverage a -> Coverage b
(forall a b. (a -> b) -> Coverage a -> Coverage b)
-> (forall a b. a -> Coverage b -> Coverage a) -> Functor Coverage
forall a b. a -> Coverage b -> Coverage a
forall a b. (a -> b) -> Coverage a -> Coverage b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Coverage b -> Coverage a
$c<$ :: forall a b. a -> Coverage b -> Coverage a
fmap :: (a -> b) -> Coverage a -> Coverage b
$cfmap :: forall a b. (a -> b) -> Coverage a -> Coverage b
Functor, Coverage a -> Bool
(a -> m) -> Coverage a -> m
(a -> b -> b) -> b -> Coverage a -> b
(forall m. Monoid m => Coverage m -> m)
-> (forall m a. Monoid m => (a -> m) -> Coverage a -> m)
-> (forall m a. Monoid m => (a -> m) -> Coverage a -> m)
-> (forall a b. (a -> b -> b) -> b -> Coverage a -> b)
-> (forall a b. (a -> b -> b) -> b -> Coverage a -> b)
-> (forall b a. (b -> a -> b) -> b -> Coverage a -> b)
-> (forall b a. (b -> a -> b) -> b -> Coverage a -> b)
-> (forall a. (a -> a -> a) -> Coverage a -> a)
-> (forall a. (a -> a -> a) -> Coverage a -> a)
-> (forall a. Coverage a -> [a])
-> (forall a. Coverage a -> Bool)
-> (forall a. Coverage a -> Int)
-> (forall a. Eq a => a -> Coverage a -> Bool)
-> (forall a. Ord a => Coverage a -> a)
-> (forall a. Ord a => Coverage a -> a)
-> (forall a. Num a => Coverage a -> a)
-> (forall a. Num a => Coverage a -> a)
-> Foldable Coverage
forall a. Eq a => a -> Coverage a -> Bool
forall a. Num a => Coverage a -> a
forall a. Ord a => Coverage a -> a
forall m. Monoid m => Coverage m -> m
forall a. Coverage a -> Bool
forall a. Coverage a -> Int
forall a. Coverage a -> [a]
forall a. (a -> a -> a) -> Coverage a -> a
forall m a. Monoid m => (a -> m) -> Coverage a -> m
forall b a. (b -> a -> b) -> b -> Coverage a -> b
forall a b. (a -> b -> b) -> b -> Coverage a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Coverage a -> a
$cproduct :: forall a. Num a => Coverage a -> a
sum :: Coverage a -> a
$csum :: forall a. Num a => Coverage a -> a
minimum :: Coverage a -> a
$cminimum :: forall a. Ord a => Coverage a -> a
maximum :: Coverage a -> a
$cmaximum :: forall a. Ord a => Coverage a -> a
elem :: a -> Coverage a -> Bool
$celem :: forall a. Eq a => a -> Coverage a -> Bool
length :: Coverage a -> Int
$clength :: forall a. Coverage a -> Int
null :: Coverage a -> Bool
$cnull :: forall a. Coverage a -> Bool
toList :: Coverage a -> [a]
$ctoList :: forall a. Coverage a -> [a]
foldl1 :: (a -> a -> a) -> Coverage a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Coverage a -> a
foldr1 :: (a -> a -> a) -> Coverage a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Coverage a -> a
foldl' :: (b -> a -> b) -> b -> Coverage a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Coverage a -> b
foldl :: (b -> a -> b) -> b -> Coverage a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Coverage a -> b
foldr' :: (a -> b -> b) -> b -> Coverage a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Coverage a -> b
foldr :: (a -> b -> b) -> b -> Coverage a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Coverage a -> b
foldMap' :: (a -> m) -> Coverage a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Coverage a -> m
foldMap :: (a -> m) -> Coverage a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Coverage a -> m
fold :: Coverage m -> m
$cfold :: forall m. Monoid m => Coverage m -> m
Foldable, Functor Coverage
Foldable Coverage
Functor Coverage
-> Foldable Coverage
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Coverage a -> f (Coverage b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Coverage (f a) -> f (Coverage a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Coverage a -> m (Coverage b))
-> (forall (m :: * -> *) a.
    Monad m =>
    Coverage (m a) -> m (Coverage a))
-> Traversable Coverage
(a -> f b) -> Coverage a -> f (Coverage b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Coverage (m a) -> m (Coverage a)
forall (f :: * -> *) a.
Applicative f =>
Coverage (f a) -> f (Coverage a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Coverage a -> m (Coverage b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Coverage a -> f (Coverage b)
sequence :: Coverage (m a) -> m (Coverage a)
$csequence :: forall (m :: * -> *) a. Monad m => Coverage (m a) -> m (Coverage a)
mapM :: (a -> m b) -> Coverage a -> m (Coverage b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Coverage a -> m (Coverage b)
sequenceA :: Coverage (f a) -> f (Coverage a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Coverage (f a) -> f (Coverage a)
traverse :: (a -> f b) -> Coverage a -> f (Coverage b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Coverage a -> f (Coverage b)
$cp2Traversable :: Foldable Coverage
$cp1Traversable :: Functor Coverage
Traversable)

------------------------------------------------------------------------
-- TestT

instance Monad m => Monad (TestT m) where
  return :: a -> TestT m a
return =
    a -> TestT m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure

  >>= :: TestT m a -> (a -> TestT m b) -> TestT m b
(>>=) TestT m a
m a -> TestT m b
k =
    ExceptT Failure (WriterT Journal m) b -> TestT m b
forall (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT (ExceptT Failure (WriterT Journal m) b -> TestT m b)
-> ExceptT Failure (WriterT Journal m) b -> TestT m b
forall a b. (a -> b) -> a -> b
$
      TestT m a -> ExceptT Failure (WriterT Journal m) a
forall (m :: * -> *) a.
TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest TestT m a
m ExceptT Failure (WriterT Journal m) a
-> (a -> ExceptT Failure (WriterT Journal m) b)
-> ExceptT Failure (WriterT Journal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      TestT m b -> ExceptT Failure (WriterT Journal m) b
forall (m :: * -> *) a.
TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest (TestT m b -> ExceptT Failure (WriterT Journal m) b)
-> (a -> TestT m b) -> a -> ExceptT Failure (WriterT Journal m) b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> TestT m b
k

instance Monad m => MonadFail (TestT m) where
  fail :: String -> TestT m a
fail String
err =
    ExceptT Failure (WriterT Journal m) a -> TestT m a
forall (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT (ExceptT Failure (WriterT Journal m) a -> TestT m a)
-> (Failure -> ExceptT Failure (WriterT Journal m) a)
-> Failure
-> TestT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterT Journal m (Either Failure a)
-> ExceptT Failure (WriterT Journal m) a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (WriterT Journal m (Either Failure a)
 -> ExceptT Failure (WriterT Journal m) a)
-> (Failure -> WriterT Journal m (Either Failure a))
-> Failure
-> ExceptT Failure (WriterT Journal m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Failure a -> WriterT Journal m (Either Failure a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either Failure a -> WriterT Journal m (Either Failure a))
-> (Failure -> Either Failure a)
-> Failure
-> WriterT Journal m (Either Failure a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Failure -> Either Failure a
forall a b. a -> Either a b
Left (Failure -> TestT m a) -> Failure -> TestT m a
forall a b. (a -> b) -> a -> b
$ Maybe Span -> String -> Maybe Diff -> Failure
Failure Maybe Span
forall a. Maybe a
Nothing String
err Maybe Diff
forall a. Maybe a
Nothing

instance MonadTrans TestT where
  lift :: m a -> TestT m a
lift =
    ExceptT Failure (WriterT Journal m) a -> TestT m a
forall (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT (ExceptT Failure (WriterT Journal m) a -> TestT m a)
-> (m a -> ExceptT Failure (WriterT Journal m) a)
-> m a
-> TestT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterT Journal m a -> ExceptT Failure (WriterT Journal m) a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (WriterT Journal m a -> ExceptT Failure (WriterT Journal m) a)
-> (m a -> WriterT Journal m a)
-> m a
-> ExceptT Failure (WriterT Journal m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> WriterT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift

instance MFunctor TestT where
  hoist :: (forall a. m a -> n a) -> TestT m b -> TestT n b
hoist forall a. m a -> n a
f =
    ExceptT Failure (WriterT Journal n) b -> TestT n b
forall (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT (ExceptT Failure (WriterT Journal n) b -> TestT n b)
-> (TestT m b -> ExceptT Failure (WriterT Journal n) b)
-> TestT m b
-> TestT n b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. WriterT Journal m a -> WriterT Journal n a)
-> ExceptT Failure (WriterT Journal m) b
-> ExceptT Failure (WriterT Journal n) b
forall k (t :: (* -> *) -> k -> *) (m :: * -> *) (n :: * -> *)
       (b :: k).
(MFunctor t, Monad m) =>
(forall a. m a -> n a) -> t m b -> t n b
hoist ((forall a. m a -> n a)
-> WriterT Journal m a -> WriterT Journal n a
forall k (t :: (* -> *) -> k -> *) (m :: * -> *) (n :: * -> *)
       (b :: k).
(MFunctor t, Monad m) =>
(forall a. m a -> n a) -> t m b -> t n b
hoist forall a. m a -> n a
f) (ExceptT Failure (WriterT Journal m) b
 -> ExceptT Failure (WriterT Journal n) b)
-> (TestT m b -> ExceptT Failure (WriterT Journal m) b)
-> TestT m b
-> ExceptT Failure (WriterT Journal n) b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestT m b -> ExceptT Failure (WriterT Journal m) b
forall (m :: * -> *) a.
TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest

instance MonadTransDistributive TestT where
  type Transformer t TestT m = (
      Transformer t (Lazy.WriterT Journal) m
    , Transformer t (ExceptT Failure) (Lazy.WriterT Journal m)
    )

  distributeT :: TestT (f m) a -> f (TestT m) a
distributeT =
    (forall a. ExceptT Failure (WriterT Journal m) a -> TestT m a)
-> f (ExceptT Failure (WriterT Journal m)) a -> f (TestT m) a
forall k (t :: (* -> *) -> k -> *) (m :: * -> *) (n :: * -> *)
       (b :: k).
(MFunctor t, Monad m) =>
(forall a. m a -> n a) -> t m b -> t n b
hoist forall a. ExceptT Failure (WriterT Journal m) a -> TestT m a
forall (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT (f (ExceptT Failure (WriterT Journal m)) a -> f (TestT m) a)
-> (TestT (f m) a -> f (ExceptT Failure (WriterT Journal m)) a)
-> TestT (f m) a
-> f (TestT m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    ExceptT Failure (f (WriterT Journal m)) a
-> f (ExceptT Failure (WriterT Journal m)) a
forall (g :: (* -> *) -> * -> *) (f :: (* -> *) -> * -> *)
       (m :: * -> *) a.
(MonadTransDistributive g, Transformer f g m) =>
g (f m) a -> f (g m) a
distributeT (ExceptT Failure (f (WriterT Journal m)) a
 -> f (ExceptT Failure (WriterT Journal m)) a)
-> (TestT (f m) a -> ExceptT Failure (f (WriterT Journal m)) a)
-> TestT (f m) a
-> f (ExceptT Failure (WriterT Journal m)) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    (forall a. WriterT Journal (f m) a -> f (WriterT Journal m) a)
-> ExceptT Failure (WriterT Journal (f m)) a
-> ExceptT Failure (f (WriterT Journal m)) a
forall k (t :: (* -> *) -> k -> *) (m :: * -> *) (n :: * -> *)
       (b :: k).
(MFunctor t, Monad m) =>
(forall a. m a -> n a) -> t m b -> t n b
hoist forall a. WriterT Journal (f m) a -> f (WriterT Journal m) a
forall (g :: (* -> *) -> * -> *) (f :: (* -> *) -> * -> *)
       (m :: * -> *) a.
(MonadTransDistributive g, Transformer f g m) =>
g (f m) a -> f (g m) a
distributeT (ExceptT Failure (WriterT Journal (f m)) a
 -> ExceptT Failure (f (WriterT Journal m)) a)
-> (TestT (f m) a -> ExceptT Failure (WriterT Journal (f m)) a)
-> TestT (f m) a
-> ExceptT Failure (f (WriterT Journal m)) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    TestT (f m) a -> ExceptT Failure (WriterT Journal (f m)) a
forall (m :: * -> *) a.
TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest

instance PrimMonad m => PrimMonad (TestT m) where
  type PrimState (TestT m) =
    PrimState m
  primitive :: (State# (PrimState (TestT m))
 -> (# State# (PrimState (TestT m)), a #))
-> TestT m a
primitive =
    m a -> TestT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> TestT m a)
-> ((State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a)
-> (State# (PrimState m) -> (# State# (PrimState m), a #))
-> TestT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive

-- FIXME instance MonadWriter w m => MonadWriter w (TestT m)

instance MonadError e m => MonadError e (TestT m) where
  throwError :: e -> TestT m a
throwError =
    m a -> TestT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> TestT m a) -> (e -> m a) -> e -> TestT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError
  catchError :: TestT m a -> (e -> TestT m a) -> TestT m a
catchError TestT m a
m e -> TestT m a
onErr =
    ExceptT Failure (WriterT Journal m) a -> TestT m a
forall (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT (ExceptT Failure (WriterT Journal m) a -> TestT m a)
-> (WriterT Journal m (Either Failure a)
    -> ExceptT Failure (WriterT Journal m) a)
-> WriterT Journal m (Either Failure a)
-> TestT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterT Journal m (Either Failure a)
-> ExceptT Failure (WriterT Journal m) a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (WriterT Journal m (Either Failure a) -> TestT m a)
-> WriterT Journal m (Either Failure a) -> TestT m a
forall a b. (a -> b) -> a -> b
$
      (ExceptT Failure (WriterT Journal m) a
-> WriterT Journal m (Either Failure a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT Failure (WriterT Journal m) a
 -> WriterT Journal m (Either Failure a))
-> ExceptT Failure (WriterT Journal m) a
-> WriterT Journal m (Either Failure a)
forall a b. (a -> b) -> a -> b
$ TestT m a -> ExceptT Failure (WriterT Journal m) a
forall (m :: * -> *) a.
TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest TestT m a
m) WriterT Journal m (Either Failure a)
-> (e -> WriterT Journal m (Either Failure a))
-> WriterT Journal m (Either Failure a)
forall e (m :: * -> *) a.
MonadError e m =>
m a -> (e -> m a) -> m a
`catchError`
      (ExceptT Failure (WriterT Journal m) a
-> WriterT Journal m (Either Failure a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT Failure (WriterT Journal m) a
 -> WriterT Journal m (Either Failure a))
-> (e -> ExceptT Failure (WriterT Journal m) a)
-> e
-> WriterT Journal m (Either Failure a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestT m a -> ExceptT Failure (WriterT Journal m) a
forall (m :: * -> *) a.
TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest (TestT m a -> ExceptT Failure (WriterT Journal m) a)
-> (e -> TestT m a) -> e -> ExceptT Failure (WriterT Journal m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> TestT m a
onErr)

instance MonadResource m => MonadResource (TestT m) where
  liftResourceT :: ResourceT IO a -> TestT m a
liftResourceT =
    m a -> TestT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> TestT m a)
-> (ResourceT IO a -> m a) -> ResourceT IO a -> TestT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ResourceT IO a -> m a
forall (m :: * -> *) a. MonadResource m => ResourceT IO a -> m a
liftResourceT

instance MonadTransControl TestT where
  type StT TestT a =
    (Either Failure a, Journal)

  liftWith :: (Run TestT -> m a) -> TestT m a
liftWith Run TestT -> m a
f =
    m (Either Failure a, Journal) -> TestT m a
forall (m :: * -> *) a. m (Either Failure a, Journal) -> TestT m a
mkTestT (m (Either Failure a, Journal) -> TestT m a)
-> (m a -> m (Either Failure a, Journal)) -> m a -> TestT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either Failure a -> (Either Failure a, Journal))
-> m (Either Failure a) -> m (Either Failure a, Journal)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (, Journal
forall a. Monoid a => a
mempty) (m (Either Failure a) -> m (Either Failure a, Journal))
-> (m a -> m (Either Failure a))
-> m a
-> m (Either Failure a, Journal)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Either Failure a) -> m a -> m (Either Failure a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Either Failure a
forall a b. b -> Either a b
Right (m a -> TestT m a) -> m a -> TestT m a
forall a b. (a -> b) -> a -> b
$ Run TestT -> m a
f (Run TestT -> m a) -> Run TestT -> m a
forall a b. (a -> b) -> a -> b
$ Run TestT
forall (m :: * -> *) a. TestT m a -> m (Either Failure a, Journal)
runTestT

  restoreT :: m (StT TestT a) -> TestT m a
restoreT =
    m (StT TestT a) -> TestT m a
forall (m :: * -> *) a. m (Either Failure a, Journal) -> TestT m a
mkTestT

instance MonadBaseControl b m => MonadBaseControl b (TestT m) where
  type StM (TestT m) a =
    ComposeSt TestT m a

  liftBaseWith :: (RunInBase (TestT m) b -> b a) -> TestT m a
liftBaseWith =
    (RunInBase (TestT m) b -> b a) -> TestT m a
forall (t :: (* -> *) -> * -> *) (b :: * -> *) (m :: * -> *) a.
(MonadTransControl t, MonadBaseControl b m) =>
(RunInBaseDefault t m b -> b a) -> t m a
defaultLiftBaseWith

  restoreM :: StM (TestT m) a -> TestT m a
restoreM =
    StM (TestT m) a -> TestT m a
forall (t :: (* -> *) -> * -> *) (b :: * -> *) (m :: * -> *) a.
(MonadTransControl t, MonadBaseControl b m) =>
ComposeSt t m a -> t m a
defaultRestoreM

class Monad m => MonadTest m where
  liftTest :: Test a -> m a

instance Monad m => MonadTest (TestT m) where
  liftTest :: Test a -> TestT m a
liftTest =
    (forall a. Identity a -> m a) -> Test a -> TestT m a
forall k (t :: (* -> *) -> k -> *) (m :: * -> *) (n :: * -> *)
       (b :: k).
(MFunctor t, Monad m) =>
(forall a. m a -> n a) -> t m b -> t n b
hoist (a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> m a) -> (Identity a -> a) -> Identity a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity a -> a
forall a. Identity a -> a
runIdentity)

instance MonadTest m => MonadTest (IdentityT m) where
  liftTest :: Test a -> IdentityT m a
liftTest =
    m a -> IdentityT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> IdentityT m a)
-> (Test a -> m a) -> Test a -> IdentityT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test a -> m a
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest

instance MonadTest m => MonadTest (MaybeT m) where
  liftTest :: Test a -> MaybeT m a
liftTest =
    m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> MaybeT m a) -> (Test a -> m a) -> Test a -> MaybeT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test a -> m a
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest

instance MonadTest m => MonadTest (ExceptT x m) where
  liftTest :: Test a -> ExceptT x m a
liftTest =
    m a -> ExceptT x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ExceptT x m a)
-> (Test a -> m a) -> Test a -> ExceptT x m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test a -> m a
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest

instance MonadTest m => MonadTest (ReaderT r m) where
  liftTest :: Test a -> ReaderT r m a
liftTest =
    m a -> ReaderT r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ReaderT r m a)
-> (Test a -> m a) -> Test a -> ReaderT r m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test a -> m a
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest

instance MonadTest m => MonadTest (Lazy.StateT s m) where
  liftTest :: Test a -> StateT s m a
liftTest =
    m a -> StateT s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> StateT s m a) -> (Test a -> m a) -> Test a -> StateT s m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test a -> m a
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest

instance MonadTest m => MonadTest (Strict.StateT s m) where
  liftTest :: Test a -> StateT s m a
liftTest =
    m a -> StateT s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> StateT s m a) -> (Test a -> m a) -> Test a -> StateT s m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test a -> m a
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest

instance (MonadTest m, Monoid w) => MonadTest (Lazy.WriterT w m) where
  liftTest :: Test a -> WriterT w m a
liftTest =
    m a -> WriterT w m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> WriterT w m a)
-> (Test a -> m a) -> Test a -> WriterT w m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test a -> m a
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest

instance (MonadTest m, Monoid w) => MonadTest (Strict.WriterT w m) where
  liftTest :: Test a -> WriterT w m a
liftTest =
    m a -> WriterT w m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> WriterT w m a)
-> (Test a -> m a) -> Test a -> WriterT w m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test a -> m a
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest

instance (MonadTest m, Monoid w) => MonadTest (Lazy.RWST r w s m) where
  liftTest :: Test a -> RWST r w s m a
liftTest =
    m a -> RWST r w s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> RWST r w s m a)
-> (Test a -> m a) -> Test a -> RWST r w s m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test a -> m a
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest

instance (MonadTest m, Monoid w) => MonadTest (Strict.RWST r w s m) where
  liftTest :: Test a -> RWST r w s m a
liftTest =
    m a -> RWST r w s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> RWST r w s m a)
-> (Test a -> m a) -> Test a -> RWST r w s m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test a -> m a
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest

instance MonadTest m => MonadTest (ContT r m) where
  liftTest :: Test a -> ContT r m a
liftTest =
    m a -> ContT r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ContT r m a) -> (Test a -> m a) -> Test a -> ContT r m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test a -> m a
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest

instance MonadTest m => MonadTest (ResourceT m) where
  liftTest :: Test a -> ResourceT m a
liftTest =
    m a -> ResourceT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ResourceT m a)
-> (Test a -> m a) -> Test a -> ResourceT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test a -> m a
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest

mkTestT :: m (Either Failure a, Journal) -> TestT m a
mkTestT :: m (Either Failure a, Journal) -> TestT m a
mkTestT =
  ExceptT Failure (WriterT Journal m) a -> TestT m a
forall (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT (ExceptT Failure (WriterT Journal m) a -> TestT m a)
-> (m (Either Failure a, Journal)
    -> ExceptT Failure (WriterT Journal m) a)
-> m (Either Failure a, Journal)
-> TestT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterT Journal m (Either Failure a)
-> ExceptT Failure (WriterT Journal m) a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (WriterT Journal m (Either Failure a)
 -> ExceptT Failure (WriterT Journal m) a)
-> (m (Either Failure a, Journal)
    -> WriterT Journal m (Either Failure a))
-> m (Either Failure a, Journal)
-> ExceptT Failure (WriterT Journal m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (Either Failure a, Journal)
-> WriterT Journal m (Either Failure a)
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Lazy.WriterT

mkTest :: (Either Failure a, Journal) -> Test a
mkTest :: (Either Failure a, Journal) -> Test a
mkTest =
  Identity (Either Failure a, Journal) -> Test a
forall (m :: * -> *) a. m (Either Failure a, Journal) -> TestT m a
mkTestT (Identity (Either Failure a, Journal) -> Test a)
-> ((Either Failure a, Journal)
    -> Identity (Either Failure a, Journal))
-> (Either Failure a, Journal)
-> Test a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either Failure a, Journal) -> Identity (Either Failure a, Journal)
forall a. a -> Identity a
Identity

runTestT :: TestT m a -> m (Either Failure a, Journal)
runTestT :: TestT m a -> m (Either Failure a, Journal)
runTestT =
  WriterT Journal m (Either Failure a)
-> m (Either Failure a, Journal)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
Lazy.runWriterT (WriterT Journal m (Either Failure a)
 -> m (Either Failure a, Journal))
-> (TestT m a -> WriterT Journal m (Either Failure a))
-> TestT m a
-> m (Either Failure a, Journal)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExceptT Failure (WriterT Journal m) a
-> WriterT Journal m (Either Failure a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT Failure (WriterT Journal m) a
 -> WriterT Journal m (Either Failure a))
-> (TestT m a -> ExceptT Failure (WriterT Journal m) a)
-> TestT m a
-> WriterT Journal m (Either Failure a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestT m a -> ExceptT Failure (WriterT Journal m) a
forall (m :: * -> *) a.
TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest

runTest :: Test a -> (Either Failure a, Journal)
runTest :: Test a -> (Either Failure a, Journal)
runTest =
  Identity (Either Failure a, Journal) -> (Either Failure a, Journal)
forall a. Identity a -> a
runIdentity (Identity (Either Failure a, Journal)
 -> (Either Failure a, Journal))
-> (Test a -> Identity (Either Failure a, Journal))
-> Test a
-> (Either Failure a, Journal)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test a -> Identity (Either Failure a, Journal)
forall (m :: * -> *) a. TestT m a -> m (Either Failure a, Journal)
runTestT

-- | Log some information which might be relevant to a potential test failure.
--
writeLog :: MonadTest m => Log -> m ()
writeLog :: Log -> m ()
writeLog Log
x =
  Test () -> m ()
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest (Test () -> m ()) -> Test () -> m ()
forall a b. (a -> b) -> a -> b
$ (Either Failure (), Journal) -> Test ()
forall a. (Either Failure a, Journal) -> Test a
mkTest (() -> Either Failure ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (), ([Log] -> Journal
Journal [Log
x]))

-- | Fail the test with an error message, useful for building other failure
--   combinators.
--
failWith :: (MonadTest m, HasCallStack) => Maybe Diff -> String -> m a
failWith :: Maybe Diff -> String -> m a
failWith Maybe Diff
mdiff String
msg =
  Test a -> m a
forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest (Test a -> m a) -> Test a -> m a
forall a b. (a -> b) -> a -> b
$ (Either Failure a, Journal) -> Test a
forall a. (Either Failure a, Journal) -> Test a
mkTest (Failure -> Either Failure a
forall a b. a -> Either a b
Left (Failure -> Either Failure a) -> Failure -> Either Failure a
forall a b. (a -> b) -> a -> b
$ Maybe Span -> String -> Maybe Diff -> Failure
Failure (CallStack -> Maybe Span
getCaller CallStack
HasCallStack => CallStack
callStack) String
msg Maybe Diff
mdiff, Journal
forall a. Monoid a => a
mempty)

-- | Annotates the source code with a message that might be useful for
--   debugging a test failure.
--
annotate :: (MonadTest m, HasCallStack) => String -> m ()
annotate :: String -> m ()
annotate String
x = do
  Log -> m ()
forall (m :: * -> *). MonadTest m => Log -> m ()
writeLog (Log -> m ()) -> Log -> m ()
forall a b. (a -> b) -> a -> b
$ Maybe Span -> String -> Log
Annotation (CallStack -> Maybe Span
getCaller CallStack
HasCallStack => CallStack
callStack) String
x

-- | Annotates the source code with a value that might be useful for
--   debugging a test failure.
--
annotateShow :: (MonadTest m, Show a, HasCallStack) => a -> m ()
annotateShow :: a -> m ()
annotateShow a
x = do
  (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m ()) -> m ()) -> (HasCallStack => m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ String -> m ()
forall (m :: * -> *). (MonadTest m, HasCallStack) => String -> m ()
annotate (a -> String
forall a. Show a => a -> String
showPretty a
x)

-- | Logs a message to be displayed as additional information in the footer of
--   the failure report.
--
footnote :: MonadTest m => String -> m ()
footnote :: String -> m ()
footnote =
  Log -> m ()
forall (m :: * -> *). MonadTest m => Log -> m ()
writeLog (Log -> m ()) -> (String -> Log) -> String -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Log
Footnote

-- | Logs a value to be displayed as additional information in the footer of
--   the failure report.
--
footnoteShow :: (MonadTest m, Show a) => a -> m ()
footnoteShow :: a -> m ()
footnoteShow =
  Log -> m ()
forall (m :: * -> *). MonadTest m => Log -> m ()
writeLog (Log -> m ()) -> (a -> Log) -> a -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Log
Footnote (String -> Log) -> (a -> String) -> a -> Log
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
showPretty

-- | Fails with an error that shows the difference between two values.
failDiff :: (MonadTest m, Show a, Show b, HasCallStack) => a -> b -> m ()
failDiff :: a -> b -> m ()
failDiff a
x b
y =
  case Value -> Value -> ValueDiff
valueDiff (Value -> Value -> ValueDiff)
-> Maybe Value -> Maybe (Value -> ValueDiff)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Value
forall a. Show a => a -> Maybe Value
mkValue a
x Maybe (Value -> ValueDiff) -> Maybe Value -> Maybe ValueDiff
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe Value
forall a. Show a => a -> Maybe Value
mkValue b
y of
    Maybe ValueDiff
Nothing ->
      (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m ()) -> m ()) -> (HasCallStack => m ()) -> m ()
forall a b. (a -> b) -> a -> b
$
        Maybe Diff -> String -> m ()
forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith Maybe Diff
forall a. Maybe a
Nothing (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$
        [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [
            String
"Failed"
          , String
"━━ lhs ━━"
          , a -> String
forall a. Show a => a -> String
showPretty a
x
          , String
"━━ rhs ━━"
          , b -> String
forall a. Show a => a -> String
showPretty b
y
          ]

    Just vdiff :: ValueDiff
vdiff@(ValueSame Value
_) ->
      (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m ()) -> m ()) -> (HasCallStack => m ()) -> m ()
forall a b. (a -> b) -> a -> b
$
        Maybe Diff -> String -> m ()
forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith (Diff -> Maybe Diff
forall a. a -> Maybe a
Just (Diff -> Maybe Diff) -> Diff -> Maybe Diff
forall a b. (a -> b) -> a -> b
$
          String -> String -> String -> String -> String -> ValueDiff -> Diff
Diff String
"━━━ Failed ("  String
"" String
"no differences" String
"" String
") ━━━" ValueDiff
vdiff) String
""

    Just ValueDiff
vdiff ->
      (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m ()) -> m ()) -> (HasCallStack => m ()) -> m ()
forall a b. (a -> b) -> a -> b
$
        Maybe Diff -> String -> m ()
forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith (Diff -> Maybe Diff
forall a. a -> Maybe a
Just (Diff -> Maybe Diff) -> Diff -> Maybe Diff
forall a b. (a -> b) -> a -> b
$
          String -> String -> String -> String -> String -> ValueDiff -> Diff
Diff String
"━━━ Failed (" String
"- lhs" String
") (" String
"+ rhs" String
") ━━━" ValueDiff
vdiff) String
""

-- | Fails with an error which renders the type of an exception and its error
--   message.
--
failException :: (MonadTest m, HasCallStack) => SomeException -> m a
failException :: SomeException -> m a
failException SomeException
x =
  (HasCallStack => m a) -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m a) -> m a) -> (HasCallStack => m a) -> m a
forall a b. (a -> b) -> a -> b
$
    [String] -> SomeException -> m a
forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
[String] -> SomeException -> m a
failExceptionWith [] SomeException
x

-- | Fails with an error which renders the given messages, the type of an exception,
--   and its error message.
--
failExceptionWith :: (MonadTest m, HasCallStack) => [String] -> SomeException -> m a
failExceptionWith :: [String] -> SomeException -> m a
failExceptionWith [String]
messages (SomeException e
x) =
  (HasCallStack => Maybe Diff -> String -> m a)
-> Maybe Diff -> String -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack
    HasCallStack => Maybe Diff -> String -> m a
forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith Maybe Diff
forall a. Maybe a
Nothing (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
messages [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [
        String
"━━━ Exception (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (e -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf e
x) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
") ━━━"
      , (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
List.dropWhileEnd Char -> Bool
Char.isSpace (e -> String
forall e. Exception e => e -> String
displayException e
x)
      ]

-- | Causes a test to fail.
--
failure :: (MonadTest m, HasCallStack) => m a
failure :: m a
failure =
  (HasCallStack => m a) -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m a) -> m a) -> (HasCallStack => m a) -> m a
forall a b. (a -> b) -> a -> b
$ Maybe Diff -> String -> m a
forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith Maybe Diff
forall a. Maybe a
Nothing String
""

-- | Another name for @pure ()@.
--
success :: MonadTest m => m ()
success :: m ()
success =
  () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

-- | Fails the test if the condition provided is 'False'.
--
assert :: (MonadTest m, HasCallStack) => Bool -> m ()
assert :: Bool -> m ()
assert Bool
b = do
  Bool
ok <- (HasCallStack => m Bool) -> m Bool
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m Bool) -> m Bool)
-> (HasCallStack => m Bool) -> m Bool
forall a b. (a -> b) -> a -> b
$ Bool -> m Bool
forall (m :: * -> *) a. (MonadTest m, HasCallStack) => a -> m a
eval Bool
b
  if Bool
ok then
    m ()
forall (m :: * -> *). MonadTest m => m ()
success
  else
    (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack HasCallStack => m ()
forall (m :: * -> *) a. (MonadTest m, HasCallStack) => m a
failure

-- | Fails the test and shows a git-like diff if the comparison operation
--   evaluates to 'False' when applied to its arguments.
--
--   The comparison function is the second argument, which may be
--   counter-intuitive to Haskell programmers. However, it allows operators to
--   be written infix for easy reading:
--
-- @
--   diff y (<) 87
--   diff x (<=) 'r'
-- @
--
--   This function behaves like the unix @diff@ tool, which gives a 0 exit
--   code if the compared files are identical, or a 1 exit code code
--   otherwise. Like unix @diff@, if the arguments fail the comparison, a
--   /diff is shown.
--
diff :: (MonadTest m, Show a, Show b, HasCallStack) => a -> (a -> b -> Bool) -> b -> m ()
diff :: a -> (a -> b -> Bool) -> b -> m ()
diff a
x a -> b -> Bool
op b
y = do
  Bool
ok <- (HasCallStack => m Bool) -> m Bool
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m Bool) -> m Bool)
-> (HasCallStack => m Bool) -> m Bool
forall a b. (a -> b) -> a -> b
$ Bool -> m Bool
forall (m :: * -> *) a. (MonadTest m, HasCallStack) => a -> m a
eval (a
x a -> b -> Bool
`op` b
y)
  if Bool
ok then
    m ()
forall (m :: * -> *). MonadTest m => m ()
success
  else
    (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m ()) -> m ()) -> (HasCallStack => m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ a -> b -> m ()
forall (m :: * -> *) a b.
(MonadTest m, Show a, Show b, HasCallStack) =>
a -> b -> m ()
failDiff a
x b
y

infix 4 ===

-- | Fails the test if the two arguments provided are not equal.
--
(===) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m ()
=== :: a -> a -> m ()
(===) a
x a
y =
  (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m ()) -> m ()) -> (HasCallStack => m ()) -> m ()
forall a b. (a -> b) -> a -> b
$
    a -> (a -> a -> Bool) -> a -> m ()
forall (m :: * -> *) a b.
(MonadTest m, Show a, Show b, HasCallStack) =>
a -> (a -> b -> Bool) -> b -> m ()
diff a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==) a
y

infix 4 /==

-- | Fails the test if the two arguments provided are equal.
--
(/==) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m ()
/== :: a -> a -> m ()
(/==) a
x a
y =
  (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m ()) -> m ()) -> (HasCallStack => m ()) -> m ()
forall a b. (a -> b) -> a -> b
$
    a -> (a -> a -> Bool) -> a -> m ()
forall (m :: * -> *) a b.
(MonadTest m, Show a, Show b, HasCallStack) =>
a -> (a -> b -> Bool) -> b -> m ()
diff a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(/=) a
y

-- | Fails the test if the value throws an exception when evaluated to weak
--   head normal form (WHNF).
--
eval :: (MonadTest m, HasCallStack) => a -> m a
eval :: a -> m a
eval a
x =
  (SomeException -> m a)
-> (a -> m a) -> Either SomeException a -> m a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ((HasCallStack => SomeException -> m a) -> SomeException -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack HasCallStack => SomeException -> m a
forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
SomeException -> m a
failException) a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Either SomeException a
forall a. a -> Either SomeException a
tryEvaluate a
x)

-- | Fails the test if the value throws an exception when evaluated to
--   normal form (NF).
--
evalNF :: (MonadTest m, NFData a, HasCallStack) => a -> m a
evalNF :: a -> m a
evalNF a
x =
  let
    messages :: [String]
messages =
      [String
"━━━ Value could not be evaluated to normal form ━━━"]
  in
    (SomeException -> m ())
-> (() -> m ()) -> Either SomeException () -> m ()
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ((HasCallStack => SomeException -> m ()) -> SomeException -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ([String] -> SomeException -> m ()
forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
[String] -> SomeException -> m a
failExceptionWith [String]
messages)) () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> Either SomeException ()
forall a. a -> Either SomeException a
tryEvaluate (a -> ()
forall a. NFData a => a -> ()
rnf a
x)) m () -> a -> m a
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> a
x

-- | Fails the test if the action throws an exception.
--
--   /The benefit of using this over simply letting the exception bubble up is/
--   /that the location of the closest 'evalM' will be shown in the output./
--
evalM :: (MonadTest m, MonadCatch m, HasCallStack) => m a -> m a
evalM :: m a -> m a
evalM m a
m =
  (SomeException -> m a)
-> (a -> m a) -> Either SomeException a -> m a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ((HasCallStack => SomeException -> m a) -> SomeException -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack HasCallStack => SomeException -> m a
forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
SomeException -> m a
failException) a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either SomeException a -> m a)
-> m (Either SomeException a) -> m a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< m a -> m (Either SomeException a)
forall (m :: * -> *) a.
MonadCatch m =>
m a -> m (Either SomeException a)
tryAll m a
m

-- | Fails the test if the 'IO' action throws an exception.
--
--   /The benefit of using this over 'liftIO' is that the location of the/
--   /exception will be shown in the output./
--
evalIO :: (MonadTest m, MonadIO m, HasCallStack) => IO a -> m a
evalIO :: IO a -> m a
evalIO IO a
m =
  (SomeException -> m a)
-> (a -> m a) -> Either SomeException a -> m a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ((HasCallStack => SomeException -> m a) -> SomeException -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack HasCallStack => SomeException -> m a
forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
SomeException -> m a
failException) a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either SomeException a -> m a)
-> m (Either SomeException a) -> m a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (Either SomeException a) -> m (Either SomeException a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> IO (Either SomeException a)
forall (m :: * -> *) a.
MonadCatch m =>
m a -> m (Either SomeException a)
tryAll IO a
m)

-- | Fails the test if the 'Either' is 'Left', otherwise returns the value in
--   the 'Right'.
--
evalEither :: (MonadTest m, Show x, HasCallStack) => Either x a -> m a
evalEither :: Either x a -> m a
evalEither = \case
  Left x
x ->
    (HasCallStack => m a) -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m a) -> m a) -> (HasCallStack => m a) -> m a
forall a b. (a -> b) -> a -> b
$ Maybe Diff -> String -> m a
forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith Maybe Diff
forall a. Maybe a
Nothing (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ x -> String
forall a. Show a => a -> String
showPretty x
x
  Right a
x ->
    a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x

-- | Fails the test if the action throws an exception, or if the
--   'Either' is 'Left', otherwise returns the value in the 'Right'.
--
evalEitherM :: (MonadTest m, Show x, MonadCatch m, HasCallStack) => m (Either x a) -> m a
evalEitherM :: m (Either x a) -> m a
evalEitherM =
  Either x a -> m a
forall (m :: * -> *) x a.
(MonadTest m, Show x, HasCallStack) =>
Either x a -> m a
evalEither (Either x a -> m a)
-> (m (Either x a) -> m (Either x a)) -> m (Either x a) -> m a
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< m (Either x a) -> m (Either x a)
forall (m :: * -> *) a.
(MonadTest m, MonadCatch m, HasCallStack) =>
m a -> m a
evalM

-- | Fails the test if the 'ExceptT' is 'Left', otherwise returns the value in
--   the 'Right'.
--
evalExceptT :: (MonadTest m, Show x, HasCallStack) => ExceptT x m a -> m a
evalExceptT :: ExceptT x m a -> m a
evalExceptT ExceptT x m a
m =
  (HasCallStack => Either x a -> m a) -> Either x a -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack HasCallStack => Either x a -> m a
forall (m :: * -> *) x a.
(MonadTest m, Show x, HasCallStack) =>
Either x a -> m a
evalEither (Either x a -> m a) -> m (Either x a) -> m a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ExceptT x m a -> m (Either x a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT x m a
m

-- | Fails the test if the 'Maybe' is 'Nothing', otherwise returns the value in
--   the 'Just'.
--
evalMaybe :: (MonadTest m, Show a, HasCallStack) => Maybe a -> m a
evalMaybe :: Maybe a -> m a
evalMaybe = \case
  Maybe a
Nothing ->
    (HasCallStack => m a) -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m a) -> m a) -> (HasCallStack => m a) -> m a
forall a b. (a -> b) -> a -> b
$ Maybe Diff -> String -> m a
forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith Maybe Diff
forall a. Maybe a
Nothing String
"the value was Nothing"
  Just a
x ->
    a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x

-- | Fails the test if the action throws an exception, or if the
--   'Maybe' is 'Nothing', otherwise returns the value in the 'Just'.
--
evalMaybeM :: (MonadTest m, Show a, MonadCatch m, HasCallStack) => m (Maybe a) -> m a
evalMaybeM :: m (Maybe a) -> m a
evalMaybeM =
  Maybe a -> m a
forall (m :: * -> *) a.
(MonadTest m, Show a, HasCallStack) =>
Maybe a -> m a
evalMaybe (Maybe a -> m a)
-> (m (Maybe a) -> m (Maybe a)) -> m (Maybe a) -> m a
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< m (Maybe a) -> m (Maybe a)
forall (m :: * -> *) a.
(MonadTest m, MonadCatch m, HasCallStack) =>
m a -> m a
evalM

------------------------------------------------------------------------
-- PropertyT

instance MonadTrans PropertyT where
  lift :: m a -> PropertyT m a
lift =
    TestT (GenT m) a -> PropertyT m a
forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT (TestT (GenT m) a -> PropertyT m a)
-> (m a -> TestT (GenT m) a) -> m a -> PropertyT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenT m a -> TestT (GenT m) a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (GenT m a -> TestT (GenT m) a)
-> (m a -> GenT m a) -> m a -> TestT (GenT m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> GenT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift

instance Monad m => MonadFail (PropertyT m) where
  fail :: String -> PropertyT m a
fail String
err =
    TestT (GenT m) a -> PropertyT m a
forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT (String -> TestT (GenT m) a
forall (m :: * -> *) a. MonadFail m => String -> m a
Fail.fail String
err)

instance MFunctor PropertyT where
  hoist :: (forall a. m a -> n a) -> PropertyT m b -> PropertyT n b
hoist forall a. m a -> n a
f =
    TestT (GenT n) b -> PropertyT n b
forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT (TestT (GenT n) b -> PropertyT n b)
-> (PropertyT m b -> TestT (GenT n) b)
-> PropertyT m b
-> PropertyT n b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. GenT m a -> GenT n a)
-> TestT (GenT m) b -> TestT (GenT n) b
forall k (t :: (* -> *) -> k -> *) (m :: * -> *) (n :: * -> *)
       (b :: k).
(MFunctor t, Monad m) =>
(forall a. m a -> n a) -> t m b -> t n b
hoist ((forall a. m a -> n a) -> GenT m a -> GenT n a
forall k (t :: (* -> *) -> k -> *) (m :: * -> *) (n :: * -> *)
       (b :: k).
(MFunctor t, Monad m) =>
(forall a. m a -> n a) -> t m b -> t n b
hoist forall a. m a -> n a
f) (TestT (GenT m) b -> TestT (GenT n) b)
-> (PropertyT m b -> TestT (GenT m) b)
-> PropertyT m b
-> TestT (GenT n) b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PropertyT m b -> TestT (GenT m) b
forall (m :: * -> *) a. PropertyT m a -> TestT (GenT m) a
unPropertyT

instance MonadTransDistributive PropertyT where
  type Transformer t PropertyT m = (
      Transformer t GenT m
    , Transformer t TestT (GenT m)
    )

  distributeT :: PropertyT (f m) a -> f (PropertyT m) a
distributeT =
    (forall a. TestT (GenT m) a -> PropertyT m a)
-> f (TestT (GenT m)) a -> f (PropertyT m) a
forall k (t :: (* -> *) -> k -> *) (m :: * -> *) (n :: * -> *)
       (b :: k).
(MFunctor t, Monad m) =>
(forall a. m a -> n a) -> t m b -> t n b
hoist forall a. TestT (GenT m) a -> PropertyT m a
forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT (f (TestT (GenT m)) a -> f (PropertyT m) a)
-> (PropertyT (f m) a -> f (TestT (GenT m)) a)
-> PropertyT (f m) a
-> f (PropertyT m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    TestT (f (GenT m)) a -> f (TestT (GenT m)) a
forall (g :: (* -> *) -> * -> *) (f :: (* -> *) -> * -> *)
       (m :: * -> *) a.
(MonadTransDistributive g, Transformer f g m) =>
g (f m) a -> f (g m) a
distributeT (TestT (f (GenT m)) a -> f (TestT (GenT m)) a)
-> (PropertyT (f m) a -> TestT (f (GenT m)) a)
-> PropertyT (f m) a
-> f (TestT (GenT m)) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    (forall a. GenT (f m) a -> f (GenT m) a)
-> TestT (GenT (f m)) a -> TestT (f (GenT m)) a
forall k (t :: (* -> *) -> k -> *) (m :: * -> *) (n :: * -> *)
       (b :: k).
(MFunctor t, Monad m) =>
(forall a. m a -> n a) -> t m b -> t n b
hoist forall a. GenT (f m) a -> f (GenT m) a
forall (g :: (* -> *) -> * -> *) (f :: (* -> *) -> * -> *)
       (m :: * -> *) a.
(MonadTransDistributive g, Transformer f g m) =>
g (f m) a -> f (g m) a
distributeT (TestT (GenT (f m)) a -> TestT (f (GenT m)) a)
-> (PropertyT (f m) a -> TestT (GenT (f m)) a)
-> PropertyT (f m) a
-> TestT (f (GenT m)) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    PropertyT (f m) a -> TestT (GenT (f m)) a
forall (m :: * -> *) a. PropertyT m a -> TestT (GenT m) a
unPropertyT

instance PrimMonad m => PrimMonad (PropertyT m) where
  type PrimState (PropertyT m) =
    PrimState m
  primitive :: (State# (PrimState (PropertyT m))
 -> (# State# (PrimState (PropertyT m)), a #))
-> PropertyT m a
primitive =
    m a -> PropertyT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> PropertyT m a)
-> ((State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a)
-> (State# (PrimState m) -> (# State# (PrimState m), a #))
-> PropertyT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive

---- FIXME instance MonadWriter w m => MonadWriter w (PropertyT m)

instance Monad m => MonadTest (PropertyT m) where
  liftTest :: Test a -> PropertyT m a
liftTest =
    TestT (GenT m) a -> PropertyT m a
forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT (TestT (GenT m) a -> PropertyT m a)
-> (Test a -> TestT (GenT m) a) -> Test a -> PropertyT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Identity a -> GenT m a) -> Test a -> TestT (GenT m) a
forall k (t :: (* -> *) -> k -> *) (m :: * -> *) (n :: * -> *)
       (b :: k).
(MFunctor t, Monad m) =>
(forall a. m a -> n a) -> t m b -> t n b
hoist (a -> GenT m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> GenT m a) -> (Identity a -> a) -> Identity a -> GenT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity a -> a
forall a. Identity a -> a
runIdentity)

instance MonadPlus m => MonadPlus (PropertyT m) where
  mzero :: PropertyT m a
mzero =
    PropertyT m a
forall (m :: * -> *) a. Monad m => PropertyT m a
discard

  mplus :: PropertyT m a -> PropertyT m a -> PropertyT m a
mplus (PropertyT TestT (GenT m) a
x) (PropertyT TestT (GenT m) a
y) =
    TestT (GenT m) a -> PropertyT m a
forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT (TestT (GenT m) a -> PropertyT m a)
-> (GenT m (Either Failure a, Journal) -> TestT (GenT m) a)
-> GenT m (Either Failure a, Journal)
-> PropertyT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenT m (Either Failure a, Journal) -> TestT (GenT m) a
forall (m :: * -> *) a. m (Either Failure a, Journal) -> TestT m a
mkTestT (GenT m (Either Failure a, Journal) -> PropertyT m a)
-> GenT m (Either Failure a, Journal) -> PropertyT m a
forall a b. (a -> b) -> a -> b
$
      GenT m (Either Failure a, Journal)
-> GenT m (Either Failure a, Journal)
-> GenT m (Either Failure a, Journal)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus (TestT (GenT m) a -> GenT m (Either Failure a, Journal)
forall (m :: * -> *) a. TestT m a -> m (Either Failure a, Journal)
runTestT TestT (GenT m) a
x) (TestT (GenT m) a -> GenT m (Either Failure a, Journal)
forall (m :: * -> *) a. TestT m a -> m (Either Failure a, Journal)
runTestT TestT (GenT m) a
y)

instance MonadPlus m => Alternative (PropertyT m) where
  empty :: PropertyT m a
empty =
    PropertyT m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
  <|> :: PropertyT m a -> PropertyT m a -> PropertyT m a
(<|>) =
    PropertyT m a -> PropertyT m a -> PropertyT m a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus

-- | Generates a random input for the test by running the provided generator.
--
--   /This is a the same as 'forAllT' but allows the user to provide a custom/
--   /rendering function. This is useful for values which don't have a/
--   /'Show' instance./
--
forAllWithT :: (Monad m, HasCallStack) => (a -> String) -> GenT m a -> PropertyT m a
forAllWithT :: (a -> String) -> GenT m a -> PropertyT m a
forAllWithT a -> String
render GenT m a
gen = do
  a
x <- TestT (GenT m) a -> PropertyT m a
forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT (TestT (GenT m) a -> PropertyT m a)
-> TestT (GenT m) a -> PropertyT m a
forall a b. (a -> b) -> a -> b
$ GenT m a -> TestT (GenT m) a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift GenT m a
gen
  (HasCallStack => PropertyT m ()) -> PropertyT m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => PropertyT m ()) -> PropertyT m ())
-> (HasCallStack => PropertyT m ()) -> PropertyT m ()
forall a b. (a -> b) -> a -> b
$ String -> PropertyT m ()
forall (m :: * -> *). (MonadTest m, HasCallStack) => String -> m ()
annotate (a -> String
render a
x)
  return a
x

-- | Generates a random input for the test by running the provided generator.
--
--   /This is a the same as 'forAll' but allows the user to provide a custom/
--   /rendering function. This is useful for values which don't have a/
--   /'Show' instance./
--
forAllWith :: (Monad m, HasCallStack) => (a -> String) -> Gen a -> PropertyT m a
forAllWith :: (a -> String) -> Gen a -> PropertyT m a
forAllWith a -> String
render Gen a
gen =
  (HasCallStack => PropertyT m a) -> PropertyT m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => PropertyT m a) -> PropertyT m a)
-> (HasCallStack => PropertyT m a) -> PropertyT m a
forall a b. (a -> b) -> a -> b
$ (a -> String) -> GenT m a -> PropertyT m a
forall (m :: * -> *) a.
(Monad m, HasCallStack) =>
(a -> String) -> GenT m a -> PropertyT m a
forAllWithT a -> String
render (GenT m a -> PropertyT m a) -> GenT m a -> PropertyT m a
forall a b. (a -> b) -> a -> b
$ Gen a -> GenT m a
forall (m :: * -> *) a. Monad m => Gen a -> GenT m a
Gen.generalize Gen a
gen

-- | Generates a random input for the test by running the provided generator.
--
--
forAllT :: (Monad m, Show a, HasCallStack) => GenT m a -> PropertyT m a
forAllT :: GenT m a -> PropertyT m a
forAllT GenT m a
gen =
  (HasCallStack => PropertyT m a) -> PropertyT m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => PropertyT m a) -> PropertyT m a)
-> (HasCallStack => PropertyT m a) -> PropertyT m a
forall a b. (a -> b) -> a -> b
$ (a -> String) -> GenT m a -> PropertyT m a
forall (m :: * -> *) a.
(Monad m, HasCallStack) =>
(a -> String) -> GenT m a -> PropertyT m a
forAllWithT a -> String
forall a. Show a => a -> String
showPretty GenT m a
gen

-- | Generates a random input for the test by running the provided generator.
--
forAll :: (Monad m, Show a, HasCallStack) => Gen a -> PropertyT m a
forAll :: Gen a -> PropertyT m a
forAll Gen a
gen =
  (HasCallStack => PropertyT m a) -> PropertyT m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => PropertyT m a) -> PropertyT m a)
-> (HasCallStack => PropertyT m a) -> PropertyT m a
forall a b. (a -> b) -> a -> b
$ (a -> String) -> Gen a -> PropertyT m a
forall (m :: * -> *) a.
(Monad m, HasCallStack) =>
(a -> String) -> Gen a -> PropertyT m a
forAllWith a -> String
forall a. Show a => a -> String
showPretty Gen a
gen

-- | Discards the current test entirely.
--
discard :: Monad m => PropertyT m a
discard :: PropertyT m a
discard =
  TestT (GenT m) a -> PropertyT m a
forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT (TestT (GenT m) a -> PropertyT m a)
-> TestT (GenT m) a -> PropertyT m a
forall a b. (a -> b) -> a -> b
$ GenT m a -> TestT (GenT m) a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Gen a -> GenT m a
forall (m :: * -> *) a. Monad m => Gen a -> GenT m a
Gen.generalize Gen a
forall (m :: * -> *) a. MonadGen m => m a
Gen.discard)

-- | Lift a test in to a property.
--
--   Because both 'TestT' and 'PropertyT' have 'MonadTest' instances, this
--   function is not often required. It can however be useful for writing
--   functions directly in 'TestT' and thus gaining a 'MonadTransControl'
--   instance at the expense of not being able to generate additional inputs
--   using 'forAll'.
--
--   An example where this is useful is parallel state machine testing, as
--   'Hedgehog.Internal.State.executeParallel' requires 'MonadBaseControl' 'IO'
--   in order to be able to spawn threads in 'MonadTest'.
--
test :: Monad m => TestT m a -> PropertyT m a
test :: TestT m a -> PropertyT m a
test =
  TestT (GenT m) a -> PropertyT m a
forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT (TestT (GenT m) a -> PropertyT m a)
-> (TestT m a -> TestT (GenT m) a) -> TestT m a -> PropertyT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. m a -> GenT m a) -> TestT m a -> TestT (GenT m) a
forall k (t :: (* -> *) -> k -> *) (m :: * -> *) (n :: * -> *)
       (b :: k).
(MFunctor t, Monad m) =>
(forall a. m a -> n a) -> t m b -> t n b
hoist forall a. m a -> GenT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift

------------------------------------------------------------------------
-- Property

-- | The default configuration for a property test.
--
defaultConfig :: PropertyConfig
defaultConfig :: PropertyConfig
defaultConfig =
  PropertyConfig :: DiscardLimit
-> ShrinkLimit
-> ShrinkRetries
-> TerminationCriteria
-> PropertyConfig
PropertyConfig {
      propertyDiscardLimit :: DiscardLimit
propertyDiscardLimit =
        DiscardLimit
100
    , propertyShrinkLimit :: ShrinkLimit
propertyShrinkLimit =
        ShrinkLimit
1000
    , propertyShrinkRetries :: ShrinkRetries
propertyShrinkRetries =
        ShrinkRetries
0
    , propertyTerminationCriteria :: TerminationCriteria
propertyTerminationCriteria =
        TestLimit -> TerminationCriteria
NoConfidenceTermination TestLimit
defaultMinTests
    }

-- | The minimum amount of tests to run for a 'Property'
--
defaultMinTests :: TestLimit
defaultMinTests :: TestLimit
defaultMinTests = TestLimit
100

-- | The default confidence allows one false positive in 10^9 tests
--
defaultConfidence :: Confidence
defaultConfidence :: Confidence
defaultConfidence = Confidence
10 Confidence -> Int -> Confidence
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
9 :: Int)

-- | Map a config modification function over a property.
--
mapConfig :: (PropertyConfig -> PropertyConfig) -> Property -> Property
mapConfig :: (PropertyConfig -> PropertyConfig) -> Property -> Property
mapConfig PropertyConfig -> PropertyConfig
f (Property PropertyConfig
cfg PropertyT IO ()
t) =
  PropertyConfig -> PropertyT IO () -> Property
Property (PropertyConfig -> PropertyConfig
f PropertyConfig
cfg) PropertyT IO ()
t

-- | Make sure that the result is statistically significant in accordance to
--   the passed 'Confidence'
--
withConfidence :: Confidence -> Property -> Property
withConfidence :: Confidence -> Property -> Property
withConfidence Confidence
c =
  let
    setConfidence :: TerminationCriteria -> TerminationCriteria
setConfidence = \case
      NoEarlyTermination Confidence
_ TestLimit
tests -> Confidence -> TestLimit -> TerminationCriteria
NoEarlyTermination Confidence
c TestLimit
tests
      NoConfidenceTermination TestLimit
tests -> Confidence -> TestLimit -> TerminationCriteria
NoEarlyTermination Confidence
c TestLimit
tests
      EarlyTermination Confidence
_ TestLimit
tests -> Confidence -> TestLimit -> TerminationCriteria
EarlyTermination Confidence
c TestLimit
tests
  in
    (PropertyConfig -> PropertyConfig) -> Property -> Property
mapConfig ((PropertyConfig -> PropertyConfig) -> Property -> Property)
-> (PropertyConfig -> PropertyConfig) -> Property -> Property
forall a b. (a -> b) -> a -> b
$ \config :: PropertyConfig
config@PropertyConfig{TerminationCriteria
ShrinkRetries
ShrinkLimit
DiscardLimit
propertyTerminationCriteria :: TerminationCriteria
propertyShrinkRetries :: ShrinkRetries
propertyShrinkLimit :: ShrinkLimit
propertyDiscardLimit :: DiscardLimit
propertyTerminationCriteria :: PropertyConfig -> TerminationCriteria
propertyShrinkRetries :: PropertyConfig -> ShrinkRetries
propertyShrinkLimit :: PropertyConfig -> ShrinkLimit
propertyDiscardLimit :: PropertyConfig -> DiscardLimit
..} ->
      PropertyConfig
config
        { propertyTerminationCriteria :: TerminationCriteria
propertyTerminationCriteria =
            TerminationCriteria -> TerminationCriteria
setConfidence TerminationCriteria
propertyTerminationCriteria
        }

verifiedTermination :: Property -> Property
verifiedTermination :: Property -> Property
verifiedTermination =
  (PropertyConfig -> PropertyConfig) -> Property -> Property
mapConfig ((PropertyConfig -> PropertyConfig) -> Property -> Property)
-> (PropertyConfig -> PropertyConfig) -> Property -> Property
forall a b. (a -> b) -> a -> b
$ \config :: PropertyConfig
config@PropertyConfig{TerminationCriteria
ShrinkRetries
ShrinkLimit
DiscardLimit
propertyTerminationCriteria :: TerminationCriteria
propertyShrinkRetries :: ShrinkRetries
propertyShrinkLimit :: ShrinkLimit
propertyDiscardLimit :: DiscardLimit
propertyTerminationCriteria :: PropertyConfig -> TerminationCriteria
propertyShrinkRetries :: PropertyConfig -> ShrinkRetries
propertyShrinkLimit :: PropertyConfig -> ShrinkLimit
propertyDiscardLimit :: PropertyConfig -> DiscardLimit
..} ->
    let
      newTerminationCriteria :: TerminationCriteria
newTerminationCriteria = case TerminationCriteria
propertyTerminationCriteria of
        NoEarlyTermination Confidence
c TestLimit
tests -> Confidence -> TestLimit -> TerminationCriteria
EarlyTermination Confidence
c TestLimit
tests
        NoConfidenceTermination TestLimit
tests -> Confidence -> TestLimit -> TerminationCriteria
EarlyTermination Confidence
defaultConfidence TestLimit
tests
        EarlyTermination Confidence
c TestLimit
tests -> Confidence -> TestLimit -> TerminationCriteria
EarlyTermination Confidence
c TestLimit
tests
    in
      PropertyConfig
config { propertyTerminationCriteria :: TerminationCriteria
propertyTerminationCriteria = TerminationCriteria
newTerminationCriteria }

-- | Set the number of times a property should be executed before it is considered
--   successful.
--
--   If you have a test that does not involve any generators and thus does not
--   need to run repeatedly, you can use @withTests 1@ to define a property that
--   will only be checked once.
--
withTests :: TestLimit -> Property -> Property
withTests :: TestLimit -> Property -> Property
withTests TestLimit
n =
  let
    setTestLimit :: TestLimit -> TerminationCriteria -> TerminationCriteria
setTestLimit TestLimit
tests = \case
      NoEarlyTermination Confidence
c TestLimit
_ -> Confidence -> TestLimit -> TerminationCriteria
NoEarlyTermination Confidence
c TestLimit
tests
      NoConfidenceTermination TestLimit
_ -> TestLimit -> TerminationCriteria
NoConfidenceTermination TestLimit
tests
      EarlyTermination Confidence
c TestLimit
_ -> Confidence -> TestLimit -> TerminationCriteria
EarlyTermination Confidence
c TestLimit
tests
  in
    (PropertyConfig -> PropertyConfig) -> Property -> Property
mapConfig ((PropertyConfig -> PropertyConfig) -> Property -> Property)
-> (PropertyConfig -> PropertyConfig) -> Property -> Property
forall a b. (a -> b) -> a -> b
$ \config :: PropertyConfig
config@PropertyConfig{TerminationCriteria
ShrinkRetries
ShrinkLimit
DiscardLimit
propertyTerminationCriteria :: TerminationCriteria
propertyShrinkRetries :: ShrinkRetries
propertyShrinkLimit :: ShrinkLimit
propertyDiscardLimit :: DiscardLimit
propertyTerminationCriteria :: PropertyConfig -> TerminationCriteria
propertyShrinkRetries :: PropertyConfig -> ShrinkRetries
propertyShrinkLimit :: PropertyConfig -> ShrinkLimit
propertyDiscardLimit :: PropertyConfig -> DiscardLimit
..} ->
      PropertyConfig
config { propertyTerminationCriteria :: TerminationCriteria
propertyTerminationCriteria = TestLimit -> TerminationCriteria -> TerminationCriteria
setTestLimit TestLimit
n TerminationCriteria
propertyTerminationCriteria }

-- | Set the number of times a property is allowed to discard before the test
--   runner gives up.
--
withDiscards :: DiscardLimit -> Property -> Property
withDiscards :: DiscardLimit -> Property -> Property
withDiscards DiscardLimit
n =
  (PropertyConfig -> PropertyConfig) -> Property -> Property
mapConfig ((PropertyConfig -> PropertyConfig) -> Property -> Property)
-> (PropertyConfig -> PropertyConfig) -> Property -> Property
forall a b. (a -> b) -> a -> b
$ \PropertyConfig
config -> PropertyConfig
config { propertyDiscardLimit :: DiscardLimit
propertyDiscardLimit = DiscardLimit
n }

-- | Set the number of times a property is allowed to shrink before the test
--   runner gives up and prints the counterexample.
--
withShrinks :: ShrinkLimit -> Property -> Property
withShrinks :: ShrinkLimit -> Property -> Property
withShrinks ShrinkLimit
n =
  (PropertyConfig -> PropertyConfig) -> Property -> Property
mapConfig ((PropertyConfig -> PropertyConfig) -> Property -> Property)
-> (PropertyConfig -> PropertyConfig) -> Property -> Property
forall a b. (a -> b) -> a -> b
$ \PropertyConfig
config -> PropertyConfig
config { propertyShrinkLimit :: ShrinkLimit
propertyShrinkLimit = ShrinkLimit
n }

-- | Set the number of times a property will be executed for each shrink before
--   the test runner gives up and tries a different shrink. See 'ShrinkRetries'
--   for more information.
--
withRetries :: ShrinkRetries -> Property -> Property
withRetries :: ShrinkRetries -> Property -> Property
withRetries ShrinkRetries
n =
  (PropertyConfig -> PropertyConfig) -> Property -> Property
mapConfig ((PropertyConfig -> PropertyConfig) -> Property -> Property)
-> (PropertyConfig -> PropertyConfig) -> Property -> Property
forall a b. (a -> b) -> a -> b
$ \PropertyConfig
config -> PropertyConfig
config { propertyShrinkRetries :: ShrinkRetries
propertyShrinkRetries = ShrinkRetries
n }

-- | Creates a property with the default configuration.
--
property :: HasCallStack => PropertyT IO () -> Property
property :: PropertyT IO () -> Property
property PropertyT IO ()
m =
  PropertyConfig -> PropertyT IO () -> Property
Property PropertyConfig
defaultConfig (PropertyT IO () -> Property) -> PropertyT IO () -> Property
forall a b. (a -> b) -> a -> b
$
    (HasCallStack => PropertyT IO ()) -> PropertyT IO ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (PropertyT IO () -> PropertyT IO ()
forall (m :: * -> *) a.
(MonadTest m, MonadCatch m, HasCallStack) =>
m a -> m a
evalM PropertyT IO ()
m)

------------------------------------------------------------------------
-- Coverage

instance Semigroup Cover where
  <> :: Cover -> Cover -> Cover
(<>) Cover
NoCover Cover
NoCover =
    Cover
NoCover
  (<>) Cover
_ Cover
_ =
    Cover
Cover

instance Monoid Cover where
  mempty :: Cover
mempty =
    Cover
NoCover
  mappend :: Cover -> Cover -> Cover
mappend =
    Cover -> Cover -> Cover
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup CoverCount where
  <> :: CoverCount -> CoverCount -> CoverCount
(<>) (CoverCount Int
n0) (CoverCount Int
n1) =
    Int -> CoverCount
CoverCount (Int
n0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n1)

instance Monoid CoverCount where
  mempty :: CoverCount
mempty =
    Int -> CoverCount
CoverCount Int
0
  mappend :: CoverCount -> CoverCount -> CoverCount
mappend =
    CoverCount -> CoverCount -> CoverCount
forall a. Semigroup a => a -> a -> a
(<>)

toCoverCount :: Cover -> CoverCount
toCoverCount :: Cover -> CoverCount
toCoverCount = \case
  Cover
NoCover ->
    Int -> CoverCount
CoverCount Int
0
  Cover
Cover ->
    Int -> CoverCount
CoverCount Int
1

-- | This semigroup is right biased. The name, location and percentage from the
--   rightmost `Label` will be kept. This shouldn't be a problem since the
--   library doesn't allow setting multiple classes with the same 'ClassifierName'.
instance Semigroup a => Semigroup (Label a) where
  <> :: Label a -> Label a -> Label a
(<>) (MkLabel LabelName
_ Maybe Span
_ CoverPercentage
_ a
m0) (MkLabel LabelName
name Maybe Span
location CoverPercentage
percentage a
m1) =
    LabelName -> Maybe Span -> CoverPercentage -> a -> Label a
forall a.
LabelName -> Maybe Span -> CoverPercentage -> a -> Label a
MkLabel LabelName
name Maybe Span
location CoverPercentage
percentage (a
m0 a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
m1)

instance Semigroup a => Semigroup (Coverage a) where
  <> :: Coverage a -> Coverage a -> Coverage a
(<>) (Coverage Map LabelName (Label a)
c0) (Coverage Map LabelName (Label a)
c1) =
    Map LabelName (Label a) -> Coverage a
forall a. Map LabelName (Label a) -> Coverage a
Coverage (Map LabelName (Label a) -> Coverage a)
-> Map LabelName (Label a) -> Coverage a
forall a b. (a -> b) -> a -> b
$
      (LabelName
 -> Label a -> Map LabelName (Label a) -> Map LabelName (Label a))
-> Map LabelName (Label a)
-> Map LabelName (Label a)
-> Map LabelName (Label a)
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
Map.foldrWithKey ((Label a -> Label a -> Label a)
-> LabelName
-> Label a
-> Map LabelName (Label a)
-> Map LabelName (Label a)
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.insertWith Label a -> Label a -> Label a
forall a. Semigroup a => a -> a -> a
(<>)) Map LabelName (Label a)
c0 Map LabelName (Label a)
c1

instance (Semigroup a, Monoid a) => Monoid (Coverage a) where
  mempty :: Coverage a
mempty =
    Map LabelName (Label a) -> Coverage a
forall a. Map LabelName (Label a) -> Coverage a
Coverage Map LabelName (Label a)
forall a. Monoid a => a
mempty
  mappend :: Coverage a -> Coverage a -> Coverage a
mappend =
    Coverage a -> Coverage a -> Coverage a
forall a. Semigroup a => a -> a -> a
(<>)

coverPercentage :: TestCount -> CoverCount -> CoverPercentage
coverPercentage :: TestCount -> CoverCount -> CoverPercentage
coverPercentage (TestCount Int
tests) (CoverCount Int
count) =
  let
    percentage :: Double
    percentage :: Double
percentage =
      Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
count Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
tests Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
100

    thousandths :: Int
    thousandths :: Int
thousandths =
      Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round (Double -> Int) -> Double -> Int
forall a b. (a -> b) -> a -> b
$ Double
percentage Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
10
  in
    Double -> CoverPercentage
CoverPercentage (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
thousandths Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
10)

labelCovered :: TestCount -> Label CoverCount -> Bool
labelCovered :: TestCount -> Label CoverCount -> Bool
labelCovered TestCount
tests (MkLabel LabelName
_ Maybe Span
_ CoverPercentage
minimum_ CoverCount
population) =
  TestCount -> CoverCount -> CoverPercentage
coverPercentage TestCount
tests CoverCount
population CoverPercentage -> CoverPercentage -> Bool
forall a. Ord a => a -> a -> Bool
>= CoverPercentage
minimum_

-- | All labels are covered
coverageSuccess :: TestCount -> Coverage CoverCount -> Bool
coverageSuccess :: TestCount -> Coverage CoverCount -> Bool
coverageSuccess TestCount
tests =
  [Label CoverCount] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Label CoverCount] -> Bool)
-> (Coverage CoverCount -> [Label CoverCount])
-> Coverage CoverCount
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestCount -> Coverage CoverCount -> [Label CoverCount]
coverageFailures TestCount
tests

coverageFailures :: TestCount -> Coverage CoverCount -> [Label CoverCount]
coverageFailures :: TestCount -> Coverage CoverCount -> [Label CoverCount]
coverageFailures TestCount
tests (Coverage Map LabelName (Label CoverCount)
kvs) =
  (Label CoverCount -> Bool)
-> [Label CoverCount] -> [Label CoverCount]
forall a. (a -> Bool) -> [a] -> [a]
List.filter (Bool -> Bool
not (Bool -> Bool)
-> (Label CoverCount -> Bool) -> Label CoverCount -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestCount -> Label CoverCount -> Bool
labelCovered TestCount
tests) (Map LabelName (Label CoverCount) -> [Label CoverCount]
forall k a. Map k a -> [a]
Map.elems Map LabelName (Label CoverCount)
kvs)

-- | Is true when the test coverage satisfies the specified 'Confidence'
--   contstraint for all 'Coverage CoverCount's
confidenceSuccess :: TestCount -> Confidence -> Coverage CoverCount -> Bool
confidenceSuccess :: TestCount -> Confidence -> Coverage CoverCount -> Bool
confidenceSuccess TestCount
tests Confidence
confidence =
  let
    assertLow :: Label CoverCount -> Bool
    assertLow :: Label CoverCount -> Bool
assertLow coverCount :: Label CoverCount
coverCount@MkLabel{Maybe Span
LabelName
CoverPercentage
CoverCount
labelAnnotation :: CoverCount
labelMinimum :: CoverPercentage
labelLocation :: Maybe Span
labelName :: LabelName
labelAnnotation :: forall a. Label a -> a
labelMinimum :: forall a. Label a -> CoverPercentage
labelLocation :: forall a. Label a -> Maybe Span
labelName :: forall a. Label a -> LabelName
..} =
      (Double, Double) -> Double
forall a b. (a, b) -> a
fst (TestCount -> Confidence -> Label CoverCount -> (Double, Double)
boundsForLabel TestCount
tests Confidence
confidence Label CoverCount
coverCount)
        Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= CoverPercentage -> Double
unCoverPercentage CoverPercentage
labelMinimum Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
100.0
  in
    [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and ([Bool] -> Bool)
-> (Coverage CoverCount -> [Bool]) -> Coverage CoverCount -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Label CoverCount -> Bool) -> [Label CoverCount] -> [Bool]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Label CoverCount -> Bool
assertLow ([Label CoverCount] -> [Bool])
-> (Coverage CoverCount -> [Label CoverCount])
-> Coverage CoverCount
-> [Bool]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map LabelName (Label CoverCount) -> [Label CoverCount]
forall k a. Map k a -> [a]
Map.elems (Map LabelName (Label CoverCount) -> [Label CoverCount])
-> (Coverage CoverCount -> Map LabelName (Label CoverCount))
-> Coverage CoverCount
-> [Label CoverCount]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coverage CoverCount -> Map LabelName (Label CoverCount)
forall a. Coverage a -> Map LabelName (Label a)
coverageLabels

-- | Is true when there exists a label that is sure to have failed according to
--   the 'Confidence' constraint
confidenceFailure :: TestCount -> Confidence -> Coverage CoverCount -> Bool
confidenceFailure :: TestCount -> Confidence -> Coverage CoverCount -> Bool
confidenceFailure TestCount
tests Confidence
confidence =
  let
    assertHigh :: Label CoverCount -> Bool
    assertHigh :: Label CoverCount -> Bool
assertHigh coverCount :: Label CoverCount
coverCount@MkLabel{Maybe Span
LabelName
CoverPercentage
CoverCount
labelAnnotation :: CoverCount
labelMinimum :: CoverPercentage
labelLocation :: Maybe Span
labelName :: LabelName
labelAnnotation :: forall a. Label a -> a
labelMinimum :: forall a. Label a -> CoverPercentage
labelLocation :: forall a. Label a -> Maybe Span
labelName :: forall a. Label a -> LabelName
..} =
      (Double, Double) -> Double
forall a b. (a, b) -> b
snd (TestCount -> Confidence -> Label CoverCount -> (Double, Double)
boundsForLabel TestCount
tests Confidence
confidence Label CoverCount
coverCount)
        Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< (CoverPercentage -> Double
unCoverPercentage CoverPercentage
labelMinimum Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
100.0)
  in
    [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or ([Bool] -> Bool)
-> (Coverage CoverCount -> [Bool]) -> Coverage CoverCount -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Label CoverCount -> Bool) -> [Label CoverCount] -> [Bool]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Label CoverCount -> Bool
assertHigh ([Label CoverCount] -> [Bool])
-> (Coverage CoverCount -> [Label CoverCount])
-> Coverage CoverCount
-> [Bool]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map LabelName (Label CoverCount) -> [Label CoverCount]
forall k a. Map k a -> [a]
Map.elems (Map LabelName (Label CoverCount) -> [Label CoverCount])
-> (Coverage CoverCount -> Map LabelName (Label CoverCount))
-> Coverage CoverCount
-> [Label CoverCount]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coverage CoverCount -> Map LabelName (Label CoverCount)
forall a. Coverage a -> Map LabelName (Label a)
coverageLabels

boundsForLabel :: TestCount -> Confidence -> Label CoverCount -> (Double, Double)
boundsForLabel :: TestCount -> Confidence -> Label CoverCount -> (Double, Double)
boundsForLabel TestCount
tests Confidence
confidence MkLabel{Maybe Span
LabelName
CoverPercentage
CoverCount
labelAnnotation :: CoverCount
labelMinimum :: CoverPercentage
labelLocation :: Maybe Span
labelName :: LabelName
labelAnnotation :: forall a. Label a -> a
labelMinimum :: forall a. Label a -> CoverPercentage
labelLocation :: forall a. Label a -> Maybe Span
labelName :: forall a. Label a -> LabelName
..} =
  Integer -> Integer -> Double -> (Double, Double)
wilsonBounds
    (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ CoverCount -> Int
unCoverCount CoverCount
labelAnnotation)
    (TestCount -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral TestCount
tests)
    (Double
1 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Confidence -> Int64
unConfidence Confidence
confidence))

-- In order to get an accurate measurement with small sample sizes, we're
-- using the Wilson score interval
-- (<https://en.wikipedia.org/wiki/Binomial_proportion_confidence_interval#Wilson_score_interval
-- wikipedia>) instead of a normal approximation interval.
wilsonBounds :: Integer -> Integer -> Double -> (Double, Double)
wilsonBounds :: Integer -> Integer -> Double -> (Double, Double)
wilsonBounds Integer
positives Integer
count Double
acceptance =
  let
    p :: Double
p =
      Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double) -> Rational -> Double
forall a b. (a -> b) -> a -> b
$ Integer
positives Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
count
    n :: Double
n =
      Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
count
    z :: Double
z =
      Double -> Double
forall a. InvErf a => a -> a
invnormcdf (Double -> Double) -> Double -> Double
forall a b. (a -> b) -> a -> b
$ Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
acceptance Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
2

    midpoint :: Double
midpoint =
      Double
p Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
z Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
z Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
n)

    offset :: Double
offset =
      Double
z Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
z Double -> Double -> Double
forall a. Floating a => a -> a -> a
** Double
2 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
n) Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double -> Double
forall a. Floating a => a -> a
sqrt (Double
p Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
p) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
n Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
z Double -> Double -> Double
forall a. Floating a => a -> a -> a
** Double
2 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
4 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
n Double -> Double -> Double
forall a. Floating a => a -> a -> a
** Double
2))

    denominator :: Double
denominator =
      Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
z Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
z Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
n

    low :: Double
low =
      (Double
midpoint Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
offset) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
denominator

    high :: Double
high =
      (Double
midpoint Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
offset) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
denominator
  in
    (Double
low, Double
high)

fromLabel :: Label a -> Coverage a
fromLabel :: Label a -> Coverage a
fromLabel Label a
x =
  Map LabelName (Label a) -> Coverage a
forall a. Map LabelName (Label a) -> Coverage a
Coverage (Map LabelName (Label a) -> Coverage a)
-> Map LabelName (Label a) -> Coverage a
forall a b. (a -> b) -> a -> b
$
    LabelName -> Label a -> Map LabelName (Label a)
forall k a. k -> a -> Map k a
Map.singleton (Label a -> LabelName
forall a. Label a -> LabelName
labelName Label a
x) Label a
x

unionsCoverage :: Semigroup a => [Coverage a] -> Coverage a
unionsCoverage :: [Coverage a] -> Coverage a
unionsCoverage =
  Map LabelName (Label a) -> Coverage a
forall a. Map LabelName (Label a) -> Coverage a
Coverage (Map LabelName (Label a) -> Coverage a)
-> ([Coverage a] -> Map LabelName (Label a))
-> [Coverage a]
-> Coverage a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  (Label a -> Label a -> Label a)
-> [Map LabelName (Label a)] -> Map LabelName (Label a)
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
(a -> a -> a) -> f (Map k a) -> Map k a
Map.unionsWith Label a -> Label a -> Label a
forall a. Semigroup a => a -> a -> a
(<>) ([Map LabelName (Label a)] -> Map LabelName (Label a))
-> ([Coverage a] -> [Map LabelName (Label a)])
-> [Coverage a]
-> Map LabelName (Label a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  (Coverage a -> Map LabelName (Label a))
-> [Coverage a] -> [Map LabelName (Label a)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Coverage a -> Map LabelName (Label a)
forall a. Coverage a -> Map LabelName (Label a)
coverageLabels

journalCoverage :: Journal -> Coverage CoverCount
journalCoverage :: Journal -> Coverage CoverCount
journalCoverage (Journal [Log]
logs) =
  (Cover -> CoverCount) -> Coverage Cover -> Coverage CoverCount
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Cover -> CoverCount
toCoverCount (Coverage Cover -> Coverage CoverCount)
-> ([Coverage Cover] -> Coverage Cover)
-> [Coverage Cover]
-> Coverage CoverCount
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  [Coverage Cover] -> Coverage Cover
forall a. Semigroup a => [Coverage a] -> Coverage a
unionsCoverage ([Coverage Cover] -> Coverage CoverCount)
-> [Coverage Cover] -> Coverage CoverCount
forall a b. (a -> b) -> a -> b
$ do
    Label Label Cover
x <- [Log]
logs
    Coverage Cover -> [Coverage Cover]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Label Cover -> Coverage Cover
forall a. Label a -> Coverage a
fromLabel Label Cover
x)

-- | Require a certain percentage of the tests to be covered by the
--   classifier.
--
-- @
--    prop_with_coverage :: Property
--    prop_with_coverage =
--      property $ do
--        match <- forAll Gen.bool
--        cover 30 "True" $ match
--        cover 30 "False" $ not match
-- @
--
--   The example above requires a minimum of 30% coverage for both
--   classifiers. If these requirements are not met, it will fail the test.
--
cover :: (MonadTest m, HasCallStack) => CoverPercentage -> LabelName -> Bool -> m ()
cover :: CoverPercentage -> LabelName -> Bool -> m ()
cover CoverPercentage
minimum_ LabelName
name Bool
covered =
  let
    cover_ :: Cover
cover_ =
      if Bool
covered then
        Cover
Cover
      else
        Cover
NoCover
  in
    Log -> m ()
forall (m :: * -> *). MonadTest m => Log -> m ()
writeLog (Log -> m ()) -> (Label Cover -> Log) -> Label Cover -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Label Cover -> Log
Label (Label Cover -> m ()) -> Label Cover -> m ()
forall a b. (a -> b) -> a -> b
$
      LabelName -> Maybe Span -> CoverPercentage -> Cover -> Label Cover
forall a.
LabelName -> Maybe Span -> CoverPercentage -> a -> Label a
MkLabel LabelName
name (CallStack -> Maybe Span
getCaller CallStack
HasCallStack => CallStack
callStack) CoverPercentage
minimum_ Cover
cover_

-- | Records the proportion of tests which satisfy a given condition.
--
-- @
--    prop_with_classifier :: Property
--    prop_with_classifier =
--      property $ do
--        xs <- forAll $ Gen.list (Range.linear 0 100) Gen.alpha
--        for_ xs $ \\x -> do
--          classify "newborns" $ x == 0
--          classify "children" $ x > 0 && x < 13
--          classify "teens" $ x > 12 && x < 20
-- @
classify :: (MonadTest m, HasCallStack) => LabelName -> Bool -> m ()
classify :: LabelName -> Bool -> m ()
classify LabelName
name Bool
covered =
  (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m ()) -> m ()) -> (HasCallStack => m ()) -> m ()
forall a b. (a -> b) -> a -> b
$
    CoverPercentage -> LabelName -> Bool -> m ()
forall (m :: * -> *).
(MonadTest m, HasCallStack) =>
CoverPercentage -> LabelName -> Bool -> m ()
cover CoverPercentage
0 LabelName
name Bool
covered

-- | Add a label for each test run. It produces a table showing the percentage
--   of test runs that produced each label.
--
label :: (MonadTest m, HasCallStack) => LabelName -> m ()
label :: LabelName -> m ()
label LabelName
name =
  (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m ()) -> m ()) -> (HasCallStack => m ()) -> m ()
forall a b. (a -> b) -> a -> b
$
    CoverPercentage -> LabelName -> Bool -> m ()
forall (m :: * -> *).
(MonadTest m, HasCallStack) =>
CoverPercentage -> LabelName -> Bool -> m ()
cover CoverPercentage
0 LabelName
name Bool
True

-- | Like 'label', but uses 'Show' to render its argument for display.
--
collect :: (MonadTest m, Show a, HasCallStack) => a -> m ()
collect :: a -> m ()
collect a
x =
  (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m ()) -> m ()) -> (HasCallStack => m ()) -> m ()
forall a b. (a -> b) -> a -> b
$
    CoverPercentage -> LabelName -> Bool -> m ()
forall (m :: * -> *).
(MonadTest m, HasCallStack) =>
CoverPercentage -> LabelName -> Bool -> m ()
cover CoverPercentage
0 (String -> LabelName
LabelName (a -> String
forall a. Show a => a -> String
show a
x)) Bool
True

------------------------------------------------------------------------
-- Internal

-- $internal
--
-- These functions are exported in case you need them in a pinch, but are not
-- part of the public API and may change at any time, even as part of a minor
-- update.