{-# 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 #-} 
module Hedgehog.Internal.Property (
  
    Property(..)
  , PropertyT(..)
  , PropertyName(..)
  , PropertyConfig(..)
  , TestLimit(..)
  , TestCount(..)
  , DiscardLimit(..)
  , DiscardCount(..)
  , ShrinkLimit(..)
  , ShrinkCount(..)
  , Skip(..)
  , ShrinkPath(..)
  , ShrinkRetries(..)
  , withTests
  , withDiscards
  , withShrinks
  , withRetries
  , withSkip
  , property
  , test
  , forAll
  , forAllT
  , forAllWith
  , forAllWithT
  , defaultMinTests
  , discard
  , skipCompress
  , shrinkPathCompress
  , skipDecompress
  , shrinkPathDecompress
  
  , Group(..)
  , GroupName(..)
  , PropertyCount(..)
  
  , 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(..)
  , Label(..)
  , LabelName(..)
  , cover
  , classify
  , label
  , collect
  , coverPercentage
  , labelCovered
  , coverageSuccess
  , coverageFailures
  , journalCoverage
  , Cover(..)
  , CoverCount(..)
  , CoverPercentage(..)
  , toCoverCount
  
  , Confidence(..)
  , TerminationCriteria(..)
  , confidenceSuccess
  , confidenceFailure
  , withConfidence
  , verifiedTermination
  , defaultConfidence
  
  
  , 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)
import qualified Numeric
import           Text.Read (readMaybe)
data Property =
  Property {
      Property -> PropertyConfig
propertyConfig :: !PropertyConfig
    , Property -> PropertyT IO ()
propertyTest :: PropertyT IO ()
    }
newtype PropertyT m a =
  PropertyT {
      forall (m :: * -> *) a. PropertyT m a -> TestT (GenT m) a
unPropertyT :: TestT (GenT m) a
    } deriving (
      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
<$ :: forall a b. a -> PropertyT m b -> PropertyT m a
$c<$ :: forall (m :: * -> *) a b.
Functor m =>
a -> PropertyT m b -> PropertyT m a
fmap :: forall a b. (a -> b) -> PropertyT m a -> PropertyT m b
$cfmap :: forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> PropertyT m a -> PropertyT m b
Functor
    , 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
<* :: forall a b. 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
*> :: forall a b. 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 :: forall a b c.
(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
<*> :: forall a b. 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 :: forall a. a -> PropertyT m a
$cpure :: forall (m :: * -> *) a. Monad m => a -> PropertyT m a
Applicative
    , 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 :: forall a. a -> PropertyT m a
$creturn :: forall (m :: * -> *) a. Monad m => a -> PropertyT m a
>> :: forall a b. 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
>>= :: forall a 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
Monad
    , 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 :: forall a. IO a -> PropertyT m a
$cliftIO :: forall (m :: * -> *) a. MonadIO m => IO a -> PropertyT m a
MonadIO
    , MonadBase b
    , 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 :: forall e a. Exception e => e -> PropertyT m a
$cthrowM :: forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> PropertyT m a
MonadThrow
    , 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 :: forall e a.
Exception e =>
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
MonadCatch
    , MonadReader r
    , MonadState s
    , MonadError e
    )
deriving instance MonadResource m => MonadResource (PropertyT m)
#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
type Test =
  TestT Identity
newtype TestT m a =
  TestT {
      forall (m :: * -> *) a.
TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest :: ExceptT Failure (Lazy.WriterT Journal m) a
    } deriving (
      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
<$ :: forall a b. a -> TestT m b -> TestT m a
$c<$ :: forall (m :: * -> *) a b. Functor m => a -> TestT m b -> TestT m a
fmap :: forall a b. (a -> b) -> TestT m a -> TestT m b
$cfmap :: forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> TestT m a -> TestT m b
Functor
    , 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
<* :: forall a b. 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
*> :: forall a b. 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 :: forall a b c. (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
<*> :: forall a b. 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 :: forall a. a -> TestT m a
$cpure :: forall (m :: * -> *) a. Monad m => a -> TestT m a
Applicative
    , 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 :: forall a. IO a -> TestT m a
$cliftIO :: forall (m :: * -> *) a. MonadIO m => IO a -> TestT m a
MonadIO
    , MonadBase b
    , 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 :: forall e a. Exception e => e -> TestT m a
$cthrowM :: forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> TestT m a
MonadThrow
    , 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 :: forall e a.
Exception e =>
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
MonadCatch
    , MonadReader r
    , MonadState s
    )
newtype PropertyName =
  PropertyName {
      PropertyName -> String
unPropertyName :: String
    } deriving (PropertyName -> PropertyName -> Bool
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
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
Ord, Int -> PropertyName -> String -> String
[PropertyName] -> String -> String
PropertyName -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PropertyName] -> String -> String
$cshowList :: [PropertyName] -> String -> String
show :: PropertyName -> String
$cshow :: PropertyName -> String
showsPrec :: Int -> PropertyName -> String -> String
$cshowsPrec :: Int -> PropertyName -> String -> String
Show, String -> PropertyName
forall a. (String -> a) -> IsString a
fromString :: String -> PropertyName
$cfromString :: String -> PropertyName
IsString, NonEmpty PropertyName -> PropertyName
PropertyName -> PropertyName -> 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 :: forall b. Integral b => 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, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => PropertyName -> m Exp
forall (m :: * -> *).
Quote m =>
PropertyName -> Code m PropertyName
liftTyped :: forall (m :: * -> *).
Quote m =>
PropertyName -> Code m PropertyName
$cliftTyped :: forall (m :: * -> *).
Quote m =>
PropertyName -> Code m PropertyName
lift :: forall (m :: * -> *). Quote m => PropertyName -> m Exp
$clift :: forall (m :: * -> *). Quote m => PropertyName -> m Exp
Lift)
newtype Confidence =
  Confidence {
    Confidence -> Int64
unConfidence :: Int64
  } deriving (Confidence -> Confidence -> Bool
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
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
Ord, Int -> Confidence -> String -> String
[Confidence] -> String -> String
Confidence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Confidence] -> String -> String
$cshowList :: [Confidence] -> String -> String
show :: Confidence -> String
$cshow :: Confidence -> String
showsPrec :: Int -> Confidence -> String -> String
$cshowsPrec :: Int -> Confidence -> String -> String
Show, Integer -> Confidence
Confidence -> Confidence
Confidence -> Confidence -> 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, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Confidence -> m Exp
forall (m :: * -> *). Quote m => Confidence -> Code m Confidence
liftTyped :: forall (m :: * -> *). Quote m => Confidence -> Code m Confidence
$cliftTyped :: forall (m :: * -> *). Quote m => Confidence -> Code m Confidence
lift :: forall (m :: * -> *). Quote m => Confidence -> m Exp
$clift :: forall (m :: * -> *). Quote m => Confidence -> m Exp
Lift)
data PropertyConfig =
  PropertyConfig {
      PropertyConfig -> DiscardLimit
propertyDiscardLimit :: !DiscardLimit
    , PropertyConfig -> ShrinkLimit
propertyShrinkLimit :: !ShrinkLimit
    , PropertyConfig -> ShrinkRetries
propertyShrinkRetries :: !ShrinkRetries
    , PropertyConfig -> TerminationCriteria
propertyTerminationCriteria :: !TerminationCriteria
    
    
    , PropertyConfig -> Maybe Skip
propertySkip :: Maybe Skip
    } deriving (PropertyConfig -> PropertyConfig -> Bool
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
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
Ord, Int -> PropertyConfig -> String -> String
[PropertyConfig] -> String -> String
PropertyConfig -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PropertyConfig] -> String -> String
$cshowList :: [PropertyConfig] -> String -> String
show :: PropertyConfig -> String
$cshow :: PropertyConfig -> String
showsPrec :: Int -> PropertyConfig -> String -> String
$cshowsPrec :: Int -> PropertyConfig -> String -> String
Show, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => PropertyConfig -> m Exp
forall (m :: * -> *).
Quote m =>
PropertyConfig -> Code m PropertyConfig
liftTyped :: forall (m :: * -> *).
Quote m =>
PropertyConfig -> Code m PropertyConfig
$cliftTyped :: forall (m :: * -> *).
Quote m =>
PropertyConfig -> Code m PropertyConfig
lift :: forall (m :: * -> *). Quote m => PropertyConfig -> m Exp
$clift :: forall (m :: * -> *). Quote m => PropertyConfig -> m Exp
Lift)
newtype TestLimit =
  TestLimit Int
  deriving (TestLimit -> TestLimit -> Bool
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
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
Ord, Int -> TestLimit -> String -> String
[TestLimit] -> String -> String
TestLimit -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TestLimit] -> String -> String
$cshowList :: [TestLimit] -> String -> String
show :: TestLimit -> String
$cshow :: TestLimit -> String
showsPrec :: Int -> TestLimit -> String -> String
$cshowsPrec :: Int -> TestLimit -> String -> String
Show, Integer -> TestLimit
TestLimit -> TestLimit
TestLimit -> TestLimit -> 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]
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
TestLimit -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: TestLimit -> Rational
$ctoRational :: TestLimit -> Rational
Real, Enum TestLimit
Real 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
Integral, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => TestLimit -> m Exp
forall (m :: * -> *). Quote m => TestLimit -> Code m TestLimit
liftTyped :: forall (m :: * -> *). Quote m => TestLimit -> Code m TestLimit
$cliftTyped :: forall (m :: * -> *). Quote m => TestLimit -> Code m TestLimit
lift :: forall (m :: * -> *). Quote m => TestLimit -> m Exp
$clift :: forall (m :: * -> *). Quote m => TestLimit -> m Exp
Lift)
newtype TestCount =
  TestCount Int
  deriving (TestCount -> TestCount -> Bool
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
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
Ord, Int -> TestCount -> String -> String
[TestCount] -> String -> String
TestCount -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TestCount] -> String -> String
$cshowList :: [TestCount] -> String -> String
show :: TestCount -> String
$cshow :: TestCount -> String
showsPrec :: Int -> TestCount -> String -> String
$cshowsPrec :: Int -> TestCount -> String -> String
Show, Integer -> TestCount
TestCount -> TestCount
TestCount -> TestCount -> 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]
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
TestCount -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: TestCount -> Rational
$ctoRational :: TestCount -> Rational
Real, Enum TestCount
Real 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
Integral, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => TestCount -> m Exp
forall (m :: * -> *). Quote m => TestCount -> Code m TestCount
liftTyped :: forall (m :: * -> *). Quote m => TestCount -> Code m TestCount
$cliftTyped :: forall (m :: * -> *). Quote m => TestCount -> Code m TestCount
lift :: forall (m :: * -> *). Quote m => TestCount -> m Exp
$clift :: forall (m :: * -> *). Quote m => TestCount -> m Exp
Lift)
newtype DiscardCount =
  DiscardCount Int
  deriving (DiscardCount -> DiscardCount -> Bool
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
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
Ord, Int -> DiscardCount -> String -> String
[DiscardCount] -> String -> String
DiscardCount -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DiscardCount] -> String -> String
$cshowList :: [DiscardCount] -> String -> String
show :: DiscardCount -> String
$cshow :: DiscardCount -> String
showsPrec :: Int -> DiscardCount -> String -> String
$cshowsPrec :: Int -> DiscardCount -> String -> String
Show, Integer -> DiscardCount
DiscardCount -> DiscardCount
DiscardCount -> DiscardCount -> 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]
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
DiscardCount -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: DiscardCount -> Rational
$ctoRational :: DiscardCount -> Rational
Real, Enum DiscardCount
Real 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
Integral)
newtype DiscardLimit =
  DiscardLimit Int
  deriving (DiscardLimit -> DiscardLimit -> Bool
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
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
Ord, Int -> DiscardLimit -> String -> String
[DiscardLimit] -> String -> String
DiscardLimit -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DiscardLimit] -> String -> String
$cshowList :: [DiscardLimit] -> String -> String
show :: DiscardLimit -> String
$cshow :: DiscardLimit -> String
showsPrec :: Int -> DiscardLimit -> String -> String
$cshowsPrec :: Int -> DiscardLimit -> String -> String
Show, Integer -> DiscardLimit
DiscardLimit -> DiscardLimit
DiscardLimit -> DiscardLimit -> 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]
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
DiscardLimit -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: DiscardLimit -> Rational
$ctoRational :: DiscardLimit -> Rational
Real, Enum DiscardLimit
Real 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
Integral, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => DiscardLimit -> m Exp
forall (m :: * -> *).
Quote m =>
DiscardLimit -> Code m DiscardLimit
liftTyped :: forall (m :: * -> *).
Quote m =>
DiscardLimit -> Code m DiscardLimit
$cliftTyped :: forall (m :: * -> *).
Quote m =>
DiscardLimit -> Code m DiscardLimit
lift :: forall (m :: * -> *). Quote m => DiscardLimit -> m Exp
$clift :: forall (m :: * -> *). Quote m => DiscardLimit -> m Exp
Lift)
newtype ShrinkLimit =
  ShrinkLimit Int
  deriving (ShrinkLimit -> ShrinkLimit -> Bool
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
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
Ord, Int -> ShrinkLimit -> String -> String
[ShrinkLimit] -> String -> String
ShrinkLimit -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ShrinkLimit] -> String -> String
$cshowList :: [ShrinkLimit] -> String -> String
show :: ShrinkLimit -> String
$cshow :: ShrinkLimit -> String
showsPrec :: Int -> ShrinkLimit -> String -> String
$cshowsPrec :: Int -> ShrinkLimit -> String -> String
Show, Integer -> ShrinkLimit
ShrinkLimit -> ShrinkLimit
ShrinkLimit -> ShrinkLimit -> 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]
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
ShrinkLimit -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: ShrinkLimit -> Rational
$ctoRational :: ShrinkLimit -> Rational
Real, Enum ShrinkLimit
Real 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
Integral, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ShrinkLimit -> m Exp
forall (m :: * -> *). Quote m => ShrinkLimit -> Code m ShrinkLimit
liftTyped :: forall (m :: * -> *). Quote m => ShrinkLimit -> Code m ShrinkLimit
$cliftTyped :: forall (m :: * -> *). Quote m => ShrinkLimit -> Code m ShrinkLimit
lift :: forall (m :: * -> *). Quote m => ShrinkLimit -> m Exp
$clift :: forall (m :: * -> *). Quote m => ShrinkLimit -> m Exp
Lift)
newtype ShrinkCount =
  ShrinkCount Int
  deriving (ShrinkCount -> ShrinkCount -> Bool
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
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
Ord, Int -> ShrinkCount -> String -> String
[ShrinkCount] -> String -> String
ShrinkCount -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ShrinkCount] -> String -> String
$cshowList :: [ShrinkCount] -> String -> String
show :: ShrinkCount -> String
$cshow :: ShrinkCount -> String
showsPrec :: Int -> ShrinkCount -> String -> String
$cshowsPrec :: Int -> ShrinkCount -> String -> String
Show, Integer -> ShrinkCount
ShrinkCount -> ShrinkCount
ShrinkCount -> ShrinkCount -> 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]
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
ShrinkCount -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: ShrinkCount -> Rational
$ctoRational :: ShrinkCount -> Rational
Real, Enum ShrinkCount
Real 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
Integral)
data Skip =
  
  
    SkipNothing
  
  
  
  | SkipToTest TestCount
  
  
  
  
  
  
  
  
  | SkipToShrink TestCount ShrinkPath
  deriving (Skip -> Skip -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Skip -> Skip -> Bool
$c/= :: Skip -> Skip -> Bool
== :: Skip -> Skip -> Bool
$c== :: Skip -> Skip -> Bool
Eq, Eq Skip
Skip -> Skip -> Bool
Skip -> Skip -> Ordering
Skip -> Skip -> Skip
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 :: Skip -> Skip -> Skip
$cmin :: Skip -> Skip -> Skip
max :: Skip -> Skip -> Skip
$cmax :: Skip -> Skip -> Skip
>= :: Skip -> Skip -> Bool
$c>= :: Skip -> Skip -> Bool
> :: Skip -> Skip -> Bool
$c> :: Skip -> Skip -> Bool
<= :: Skip -> Skip -> Bool
$c<= :: Skip -> Skip -> Bool
< :: Skip -> Skip -> Bool
$c< :: Skip -> Skip -> Bool
compare :: Skip -> Skip -> Ordering
$ccompare :: Skip -> Skip -> Ordering
Ord, Int -> Skip -> String -> String
[Skip] -> String -> String
Skip -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Skip] -> String -> String
$cshowList :: [Skip] -> String -> String
show :: Skip -> String
$cshow :: Skip -> String
showsPrec :: Int -> Skip -> String -> String
$cshowsPrec :: Int -> Skip -> String -> String
Show, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Skip -> m Exp
forall (m :: * -> *). Quote m => Skip -> Code m Skip
liftTyped :: forall (m :: * -> *). Quote m => Skip -> Code m Skip
$cliftTyped :: forall (m :: * -> *). Quote m => Skip -> Code m Skip
lift :: forall (m :: * -> *). Quote m => Skip -> m Exp
$clift :: forall (m :: * -> *). Quote m => Skip -> m Exp
Lift)
instance IsString Skip where
  fromString :: String -> Skip
fromString String
s =
    case String -> Maybe Skip
skipDecompress String
s of
      Maybe Skip
Nothing ->
        forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"fromString: Not a valid Skip: " forall a. [a] -> [a] -> [a]
++ String
s
      Just Skip
skip ->
        Skip
skip
newtype ShrinkPath =
  ShrinkPath [Int]
  deriving (ShrinkPath -> ShrinkPath -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShrinkPath -> ShrinkPath -> Bool
$c/= :: ShrinkPath -> ShrinkPath -> Bool
== :: ShrinkPath -> ShrinkPath -> Bool
$c== :: ShrinkPath -> ShrinkPath -> Bool
Eq, Eq ShrinkPath
ShrinkPath -> ShrinkPath -> Bool
ShrinkPath -> ShrinkPath -> Ordering
ShrinkPath -> ShrinkPath -> ShrinkPath
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 :: ShrinkPath -> ShrinkPath -> ShrinkPath
$cmin :: ShrinkPath -> ShrinkPath -> ShrinkPath
max :: ShrinkPath -> ShrinkPath -> ShrinkPath
$cmax :: ShrinkPath -> ShrinkPath -> ShrinkPath
>= :: ShrinkPath -> ShrinkPath -> Bool
$c>= :: ShrinkPath -> ShrinkPath -> Bool
> :: ShrinkPath -> ShrinkPath -> Bool
$c> :: ShrinkPath -> ShrinkPath -> Bool
<= :: ShrinkPath -> ShrinkPath -> Bool
$c<= :: ShrinkPath -> ShrinkPath -> Bool
< :: ShrinkPath -> ShrinkPath -> Bool
$c< :: ShrinkPath -> ShrinkPath -> Bool
compare :: ShrinkPath -> ShrinkPath -> Ordering
$ccompare :: ShrinkPath -> ShrinkPath -> Ordering
Ord, Int -> ShrinkPath -> String -> String
[ShrinkPath] -> String -> String
ShrinkPath -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ShrinkPath] -> String -> String
$cshowList :: [ShrinkPath] -> String -> String
show :: ShrinkPath -> String
$cshow :: ShrinkPath -> String
showsPrec :: Int -> ShrinkPath -> String -> String
$cshowsPrec :: Int -> ShrinkPath -> String -> String
Show, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ShrinkPath -> m Exp
forall (m :: * -> *). Quote m => ShrinkPath -> Code m ShrinkPath
liftTyped :: forall (m :: * -> *). Quote m => ShrinkPath -> Code m ShrinkPath
$cliftTyped :: forall (m :: * -> *). Quote m => ShrinkPath -> Code m ShrinkPath
lift :: forall (m :: * -> *). Quote m => ShrinkPath -> m Exp
$clift :: forall (m :: * -> *). Quote m => ShrinkPath -> m Exp
Lift)
skipCompress :: Skip -> String
skipCompress :: Skip -> String
skipCompress = \case
  Skip
SkipNothing ->
    String
""
  SkipToTest (TestCount Int
n) ->
    forall a. Show a => a -> String
show Int
n
  SkipToShrink (TestCount Int
n) ShrinkPath
sp ->
    forall a. Show a => a -> String
show Int
n forall a. [a] -> [a] -> [a]
++ String
":" forall a. [a] -> [a] -> [a]
++ ShrinkPath -> String
shrinkPathCompress ShrinkPath
sp
shrinkPathCompress :: ShrinkPath -> String
shrinkPathCompress :: ShrinkPath -> String
shrinkPathCompress (ShrinkPath [Int]
sp) =
  let
    groups :: [(Int, Int)]
groups = forall a b. (a -> b) -> [a] -> [b]
List.map (\[Int]
l -> (forall a. [a] -> a
head [Int]
l, forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
l)) forall a b. (a -> b) -> a -> b
$ forall a. Eq a => [a] -> [[a]]
List.group [Int]
sp
  in
    (forall a. Monoid a => [a] -> a
mconcat
      forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
          (\String
alphabet (Int
loc, Int
count) ->
              forall a.
(Integral a, Show a) =>
a -> (Int -> Char) -> a -> String -> String
Numeric.showIntAtBase Int
26 (String
alphabet forall a. [a] -> Int -> a
!!) Int
loc
              forall a. Semigroup a => a -> a -> a
<> if Int
count forall a. Eq a => a -> a -> Bool
== Int
1 then forall a. Monoid a => a
mempty else forall a. Show a => a -> String -> String
shows Int
count
          )
          (forall a. [a] -> [a]
cycle [[Char
'a'..Char
'z'], [Char
'A'..Char
'Z']])
          [(Int, Int)]
groups
    )
      String
""
skipDecompress :: String -> Maybe Skip
skipDecompress :: String -> Maybe Skip
skipDecompress String
str =
  if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str then
    forall a. a -> Maybe a
Just Skip
SkipNothing
  else do
    let
      (String
tcStr, String
spStr)
        = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (forall a. Eq a => a -> a -> Bool
/= Char
':') String
str
    TestCount
tc <- Int -> TestCount
TestCount forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Read a => String -> Maybe a
readMaybe String
tcStr
    if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
spStr then
      forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ TestCount -> Skip
SkipToTest TestCount
tc
    else do
      ShrinkPath
sp <- String -> Maybe ShrinkPath
shrinkPathDecompress forall a b. (a -> b) -> a -> b
$ forall a. Int -> [a] -> [a]
drop Int
1 String
spStr
      forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ TestCount -> ShrinkPath -> Skip
SkipToShrink TestCount
tc ShrinkPath
sp
shrinkPathDecompress :: String -> Maybe ShrinkPath
shrinkPathDecompress :: String -> Maybe ShrinkPath
shrinkPathDecompress String
str =
  let
    isDigit :: Char -> Bool
isDigit Char
c = Char
'0' forall a. Ord a => a -> a -> Bool
<= Char
c Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'9'
    isLower :: Char -> Bool
isLower Char
c = Char
'a' forall a. Ord a => a -> a -> Bool
<= Char
c Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'z'
    isUpper :: Char -> Bool
isUpper Char
c = Char
'A' forall a. Ord a => a -> a -> Bool
<= Char
c Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'Z'
    classifyChar :: Char -> (Bool, Bool, Bool)
classifyChar Char
c = (Char -> Bool
isDigit Char
c, Char -> Bool
isLower Char
c, Char -> Bool
isUpper Char
c)
    readSNum :: String -> [(a, String)]
readSNum String
"" = []
    readSNum s :: String
s@(Char
c1:String
_) =
      if Char -> Bool
isDigit Char
c1 then
        forall a. Num a => a -> (Char -> Bool) -> (Char -> Int) -> ReadS a
Numeric.readInt a
10 Char -> Bool
isDigit (\Char
c -> forall a. Enum a => a -> Int
fromEnum Char
c forall a. Num a => a -> a -> a
- forall a. Enum a => a -> Int
fromEnum Char
'0') String
s
      else if Char -> Bool
isLower Char
c1 then
        forall a. Num a => a -> (Char -> Bool) -> (Char -> Int) -> ReadS a
Numeric.readInt a
26 Char -> Bool
isLower (\Char
c -> forall a. Enum a => a -> Int
fromEnum Char
c forall a. Num a => a -> a -> a
- forall a. Enum a => a -> Int
fromEnum Char
'a') String
s
      else if Char -> Bool
isUpper Char
c1 then
        forall a. Num a => a -> (Char -> Bool) -> (Char -> Int) -> ReadS a
Numeric.readInt a
26 Char -> Bool
isUpper (\Char
c -> forall a. Enum a => a -> Int
fromEnum Char
c forall a. Num a => a -> a -> a
- forall a. Enum a => a -> Int
fromEnum Char
'A') String
s
      else
        []
    readNumMaybe :: String -> Maybe a
readNumMaybe String
s =
      case forall {a}. Num a => String -> [(a, String)]
readSNum String
s of
        [(a
num, String
"")] -> forall a. a -> Maybe a
Just a
num
        [(a, String)]
_ -> forall a. Maybe a
Nothing
    [(Maybe Int, Maybe Int)]
spGroups :: [(Maybe Int, Maybe Int)] =
      let
        go :: String -> [(Maybe a, Maybe a)]
go [] =
          []
        go (Char
c1:String
cs) =
          let
            (String
hd, String
tl1) =
              forall a. (a -> Bool) -> [a] -> ([a], [a])
span (\Char
c -> Char -> (Bool, Bool, Bool)
classifyChar Char
c forall a. Eq a => a -> a -> Bool
== Char -> (Bool, Bool, Bool)
classifyChar Char
c1) String
cs
            (String
digs, String
tl2) =
              forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isDigit String
tl1
          in
            ( forall {a}. Num a => String -> Maybe a
readNumMaybe (Char
c1forall a. a -> [a] -> [a]
:String
hd)
            , forall {a}. Num a => String -> Maybe a
readNumMaybe forall a b. (a -> b) -> a -> b
$ if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
digs then String
"1" else String
digs
            )
            forall a. a -> [a] -> [a]
: String -> [(Maybe a, Maybe a)]
go String
tl2
      in
        forall {a} {a}. (Num a, Num a) => String -> [(Maybe a, Maybe a)]
go String
str
  in do
    [Int]
sp <- forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
      forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\(Maybe Int
mNum, Maybe Int
mCount) -> forall a. Int -> a -> [a]
replicate forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
mCount forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Int
mNum) [(Maybe Int, Maybe Int)]
spGroups
    forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [Int] -> ShrinkPath
ShrinkPath [Int]
sp
newtype ShrinkRetries =
  ShrinkRetries Int
  deriving (ShrinkRetries -> ShrinkRetries -> Bool
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
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
Ord, Int -> ShrinkRetries -> String -> String
[ShrinkRetries] -> String -> String
ShrinkRetries -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ShrinkRetries] -> String -> String
$cshowList :: [ShrinkRetries] -> String -> String
show :: ShrinkRetries -> String
$cshow :: ShrinkRetries -> String
showsPrec :: Int -> ShrinkRetries -> String -> String
$cshowsPrec :: Int -> ShrinkRetries -> String -> String
Show, Integer -> ShrinkRetries
ShrinkRetries -> ShrinkRetries
ShrinkRetries -> ShrinkRetries -> 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]
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
ShrinkRetries -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: ShrinkRetries -> Rational
$ctoRational :: ShrinkRetries -> Rational
Real, Enum ShrinkRetries
Real 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
Integral, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ShrinkRetries -> m Exp
forall (m :: * -> *).
Quote m =>
ShrinkRetries -> Code m ShrinkRetries
liftTyped :: forall (m :: * -> *).
Quote m =>
ShrinkRetries -> Code m ShrinkRetries
$cliftTyped :: forall (m :: * -> *).
Quote m =>
ShrinkRetries -> Code m ShrinkRetries
lift :: forall (m :: * -> *). Quote m => ShrinkRetries -> m Exp
$clift :: forall (m :: * -> *). Quote m => ShrinkRetries -> m Exp
Lift)
data Group =
  Group {
      Group -> GroupName
groupName :: !GroupName
    , Group -> [(PropertyName, Property)]
groupProperties :: ![(PropertyName, Property)]
    }
newtype GroupName =
  GroupName {
      GroupName -> String
unGroupName :: String
    } deriving (GroupName -> GroupName -> Bool
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
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
Ord, Int -> GroupName -> String -> String
[GroupName] -> String -> String
GroupName -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [GroupName] -> String -> String
$cshowList :: [GroupName] -> String -> String
show :: GroupName -> String
$cshow :: GroupName -> String
showsPrec :: Int -> GroupName -> String -> String
$cshowsPrec :: Int -> GroupName -> String -> String
Show, String -> GroupName
forall a. (String -> a) -> IsString a
fromString :: String -> GroupName
$cfromString :: String -> GroupName
IsString, NonEmpty GroupName -> GroupName
GroupName -> GroupName -> 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 :: forall b. Integral b => 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, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => GroupName -> m Exp
forall (m :: * -> *). Quote m => GroupName -> Code m GroupName
liftTyped :: forall (m :: * -> *). Quote m => GroupName -> Code m GroupName
$cliftTyped :: forall (m :: * -> *). Quote m => GroupName -> Code m GroupName
lift :: forall (m :: * -> *). Quote m => GroupName -> m Exp
$clift :: forall (m :: * -> *). Quote m => GroupName -> m Exp
Lift)
newtype PropertyCount =
  PropertyCount Int
  deriving (PropertyCount -> PropertyCount -> Bool
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
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
Ord, Int -> PropertyCount -> String -> String
[PropertyCount] -> String -> String
PropertyCount -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PropertyCount] -> String -> String
$cshowList :: [PropertyCount] -> String -> String
show :: PropertyCount -> String
$cshow :: PropertyCount -> String
showsPrec :: Int -> PropertyCount -> String -> String
$cshowsPrec :: Int -> PropertyCount -> String -> String
Show, Integer -> PropertyCount
PropertyCount -> PropertyCount
PropertyCount -> PropertyCount -> 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]
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
PropertyCount -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: PropertyCount -> Rational
$ctoRational :: PropertyCount -> Rational
Real, Enum PropertyCount
Real 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
Integral)
data TerminationCriteria =
    EarlyTermination Confidence TestLimit
  | NoEarlyTermination Confidence TestLimit
  | NoConfidenceTermination TestLimit
  deriving (TerminationCriteria -> TerminationCriteria -> Bool
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
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
Ord, Int -> TerminationCriteria -> String -> String
[TerminationCriteria] -> String -> String
TerminationCriteria -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TerminationCriteria] -> String -> String
$cshowList :: [TerminationCriteria] -> String -> String
show :: TerminationCriteria -> String
$cshow :: TerminationCriteria -> String
showsPrec :: Int -> TerminationCriteria -> String -> String
$cshowsPrec :: Int -> TerminationCriteria -> String -> String
Show, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => TerminationCriteria -> m Exp
forall (m :: * -> *).
Quote m =>
TerminationCriteria -> Code m TerminationCriteria
liftTyped :: forall (m :: * -> *).
Quote m =>
TerminationCriteria -> Code m TerminationCriteria
$cliftTyped :: forall (m :: * -> *).
Quote m =>
TerminationCriteria -> Code m TerminationCriteria
lift :: forall (m :: * -> *). Quote m => TerminationCriteria -> m Exp
$clift :: forall (m :: * -> *). Quote m => TerminationCriteria -> m Exp
Lift)
data Log =
    Annotation (Maybe Span) String
  |  String
  | Label (Label Cover)
    deriving (Log -> Log -> Bool
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 -> String -> String
[Log] -> String -> String
Log -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Log] -> String -> String
$cshowList :: [Log] -> String -> String
show :: Log -> String
$cshow :: Log -> String
showsPrec :: Int -> Log -> String -> String
$cshowsPrec :: Int -> Log -> String -> String
Show)
newtype Journal =
  Journal {
      Journal -> [Log]
journalLogs :: [Log]
    } deriving (Journal -> Journal -> Bool
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 -> String -> String
[Journal] -> String -> String
Journal -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Journal] -> String -> String
$cshowList :: [Journal] -> String -> String
show :: Journal -> String
$cshow :: Journal -> String
showsPrec :: Int -> Journal -> String -> String
$cshowsPrec :: Int -> Journal -> String -> String
Show, NonEmpty Journal -> Journal
Journal -> Journal -> 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 :: forall b. Integral b => 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
[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
Monoid)
data Failure =
  Failure (Maybe Span) String (Maybe Diff)
  deriving (Failure -> Failure -> Bool
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 -> String -> String
[Failure] -> String -> String
Failure -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Failure] -> String -> String
$cshowList :: [Failure] -> String -> String
show :: Failure -> String
$cshow :: Failure -> String
showsPrec :: Int -> Failure -> String -> String
$cshowsPrec :: Int -> Failure -> String -> String
Show)
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
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 -> String -> String
[Diff] -> String -> String
Diff -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Diff] -> String -> String
$cshowList :: [Diff] -> String -> String
show :: Diff -> String
$cshow :: Diff -> String
showsPrec :: Int -> Diff -> String -> String
$cshowsPrec :: Int -> Diff -> String -> String
Show)
data Cover =
    NoCover
  | Cover
    deriving (Cover -> Cover -> Bool
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
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
Ord, Int -> Cover -> String -> String
[Cover] -> String -> String
Cover -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Cover] -> String -> String
$cshowList :: [Cover] -> String -> String
show :: Cover -> String
$cshow :: Cover -> String
showsPrec :: Int -> Cover -> String -> String
$cshowsPrec :: Int -> Cover -> String -> String
Show)
newtype CoverCount =
  CoverCount {
      CoverCount -> Int
unCoverCount :: Int
    } deriving (CoverCount -> CoverCount -> Bool
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
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
Ord, Int -> CoverCount -> String -> String
[CoverCount] -> String -> String
CoverCount -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CoverCount] -> String -> String
$cshowList :: [CoverCount] -> String -> String
show :: CoverCount -> String
$cshow :: CoverCount -> String
showsPrec :: Int -> CoverCount -> String -> String
$cshowsPrec :: Int -> CoverCount -> String -> String
Show, Integer -> CoverCount
CoverCount -> CoverCount
CoverCount -> CoverCount -> 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)
newtype CoverPercentage =
  CoverPercentage {
      CoverPercentage -> Double
unCoverPercentage :: Double
    } deriving (CoverPercentage -> CoverPercentage -> Bool
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
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
Ord, Int -> CoverPercentage -> String -> String
[CoverPercentage] -> String -> String
CoverPercentage -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CoverPercentage] -> String -> String
$cshowList :: [CoverPercentage] -> String -> String
show :: CoverPercentage -> String
$cshow :: CoverPercentage -> String
showsPrec :: Int -> CoverPercentage -> String -> String
$cshowsPrec :: Int -> CoverPercentage -> String -> String
Show, Integer -> CoverPercentage
CoverPercentage -> CoverPercentage
CoverPercentage -> CoverPercentage -> 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
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
Fractional)
newtype LabelName =
  LabelName {
      LabelName -> String
unLabelName :: String
    } deriving (LabelName -> LabelName -> Bool
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
[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
Monoid, Eq 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
Ord, NonEmpty LabelName -> LabelName
LabelName -> LabelName -> 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 :: forall b. Integral b => 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 -> String -> String
[LabelName] -> String -> String
LabelName -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [LabelName] -> String -> String
$cshowList :: [LabelName] -> String -> String
show :: LabelName -> String
$cshow :: LabelName -> String
showsPrec :: Int -> LabelName -> String -> String
$cshowsPrec :: Int -> LabelName -> String -> String
Show, String -> LabelName
forall a. (String -> a) -> IsString a
fromString :: String -> LabelName
$cfromString :: String -> LabelName
IsString)
data Label a =
  MkLabel {
      forall a. Label a -> LabelName
labelName :: !LabelName
    , forall a. Label a -> Maybe Span
labelLocation :: !(Maybe Span)
    , forall a. Label a -> CoverPercentage
labelMinimum :: !CoverPercentage
    , forall a. Label a -> a
labelAnnotation :: !a
    } deriving (Label a -> Label a -> Bool
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 -> String -> String
forall a. Show a => Int -> Label a -> String -> String
forall a. Show a => [Label a] -> String -> String
forall a. Show a => Label a -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Label a] -> String -> String
$cshowList :: forall a. Show a => [Label a] -> String -> String
show :: Label a -> String
$cshow :: forall a. Show a => Label a -> String
showsPrec :: Int -> Label a -> String -> String
$cshowsPrec :: forall a. Show a => Int -> Label a -> String -> String
Show, 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
<$ :: forall a b. a -> Label b -> Label a
$c<$ :: forall a b. a -> Label b -> Label a
fmap :: forall a b. (a -> b) -> Label a -> Label b
$cfmap :: forall a b. (a -> b) -> Label a -> Label b
Functor, 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 :: forall a. Num a => Label a -> a
$cproduct :: forall a. Num a => Label a -> a
sum :: forall a. Num a => Label a -> a
$csum :: forall a. Num a => Label a -> a
minimum :: forall a. Ord a => Label a -> a
$cminimum :: forall a. Ord a => Label a -> a
maximum :: forall a. Ord a => Label a -> a
$cmaximum :: forall a. Ord a => Label a -> a
elem :: forall a. Eq a => a -> Label a -> Bool
$celem :: forall a. Eq a => a -> Label a -> Bool
length :: forall a. Label a -> Int
$clength :: forall a. Label a -> Int
null :: forall a. Label a -> Bool
$cnull :: forall a. Label a -> Bool
toList :: forall a. Label a -> [a]
$ctoList :: forall a. Label a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Label a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Label a -> a
foldr1 :: forall a. (a -> a -> a) -> Label a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Label a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> Label a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Label a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Label a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Label a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Label a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Label a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Label a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Label a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> Label a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Label a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Label a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Label a -> m
fold :: forall m. Monoid m => Label m -> m
$cfold :: forall m. Monoid m => Label m -> m
Foldable, Functor Label
Foldable Label
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 :: forall (m :: * -> *) a. Monad m => Label (m a) -> m (Label a)
$csequence :: forall (m :: * -> *) a. Monad m => Label (m a) -> m (Label a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Label a -> m (Label b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Label a -> m (Label b)
sequenceA :: forall (f :: * -> *) a. Applicative f => Label (f a) -> f (Label a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Label (f a) -> f (Label a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Label a -> f (Label b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Label a -> f (Label b)
Traversable)
newtype Coverage a =
  Coverage {
      forall a. Coverage a -> Map LabelName (Label a)
coverageLabels :: Map LabelName (Label a)
    } deriving (Coverage a -> Coverage a -> Bool
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 -> String -> String
forall a. Show a => Int -> Coverage a -> String -> String
forall a. Show a => [Coverage a] -> String -> String
forall a. Show a => Coverage a -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Coverage a] -> String -> String
$cshowList :: forall a. Show a => [Coverage a] -> String -> String
show :: Coverage a -> String
$cshow :: forall a. Show a => Coverage a -> String
showsPrec :: Int -> Coverage a -> String -> String
$cshowsPrec :: forall a. Show a => Int -> Coverage a -> String -> String
Show, 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
<$ :: forall a b. a -> Coverage b -> Coverage a
$c<$ :: forall a b. a -> Coverage b -> Coverage a
fmap :: forall a b. (a -> b) -> Coverage a -> Coverage b
$cfmap :: forall a b. (a -> b) -> Coverage a -> Coverage b
Functor, 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 :: forall a. Num a => Coverage a -> a
$cproduct :: forall a. Num a => Coverage a -> a
sum :: forall a. Num a => Coverage a -> a
$csum :: forall a. Num a => Coverage a -> a
minimum :: forall a. Ord a => Coverage a -> a
$cminimum :: forall a. Ord a => Coverage a -> a
maximum :: forall a. Ord a => Coverage a -> a
$cmaximum :: forall a. Ord a => Coverage a -> a
elem :: forall a. Eq a => a -> Coverage a -> Bool
$celem :: forall a. Eq a => a -> Coverage a -> Bool
length :: forall a. Coverage a -> Int
$clength :: forall a. Coverage a -> Int
null :: forall a. Coverage a -> Bool
$cnull :: forall a. Coverage a -> Bool
toList :: forall a. Coverage a -> [a]
$ctoList :: forall a. Coverage a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Coverage a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Coverage a -> a
foldr1 :: forall a. (a -> a -> a) -> Coverage a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Coverage a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> Coverage a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Coverage a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Coverage a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Coverage a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Coverage a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Coverage a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Coverage a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Coverage a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> Coverage a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Coverage a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Coverage a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Coverage a -> m
fold :: forall m. Monoid m => Coverage m -> m
$cfold :: forall m. Monoid m => Coverage m -> m
Foldable, Functor Coverage
Foldable Coverage
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 :: forall (m :: * -> *) a. Monad m => Coverage (m a) -> m (Coverage a)
$csequence :: forall (m :: * -> *) a. Monad m => Coverage (m a) -> m (Coverage a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Coverage a -> m (Coverage b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Coverage a -> m (Coverage b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Coverage (f a) -> f (Coverage a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Coverage (f a) -> f (Coverage a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Coverage a -> f (Coverage b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Coverage a -> f (Coverage b)
Traversable)
instance Monad m => Monad (TestT m) where
  return :: forall a. a -> TestT m a
return =
    forall (f :: * -> *) a. Applicative f => a -> f a
pure
  >>= :: forall a b. TestT m a -> (a -> TestT m b) -> TestT m b
(>>=) TestT m a
m a -> TestT m b
k =
    forall (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT forall a b. (a -> b) -> a -> b
$
      forall (m :: * -> *) a.
TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest TestT m a
m forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      forall (m :: * -> *) a.
TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> TestT m b
k
instance Monad m => MonadFail (TestT m) where
  fail :: forall a. String -> TestT m a
fail String
err =
    forall (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Maybe Span -> String -> Maybe Diff -> Failure
Failure forall a. Maybe a
Nothing String
err forall a. Maybe a
Nothing
instance MonadTrans TestT where
  lift :: forall (m :: * -> *) a. Monad m => m a -> TestT m a
lift =
    forall (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift
instance MFunctor TestT where
  hoist :: forall (m :: * -> *) (n :: * -> *) b.
Monad m =>
(forall a. m a -> n a) -> TestT m b -> TestT n b
hoist forall a. m a -> n a
f =
    forall (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 {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) forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 :: forall (f :: (* -> *) -> * -> *) (m :: * -> *) a.
Transformer f TestT m =>
TestT (f m) a -> f (TestT m) a
distributeT =
    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 (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    forall (g :: (* -> *) -> * -> *) (f :: (* -> *) -> * -> *)
       (m :: * -> *) a.
(MonadTransDistributive g, Transformer f g m) =>
g (f m) a -> f (g m) a
distributeT forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    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 (g :: (* -> *) -> * -> *) (f :: (* -> *) -> * -> *)
       (m :: * -> *) a.
(MonadTransDistributive g, Transformer f g m) =>
g (f m) a -> f (g m) a
distributeT forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    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 :: forall a.
(State# (PrimState (TestT m))
 -> (# State# (PrimState (TestT m)), a #))
-> TestT m a
primitive =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive
instance MonadError e m => MonadError e (TestT m) where
  throwError :: forall a. e -> TestT m a
throwError =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError
  catchError :: forall a. TestT m a -> (e -> TestT m a) -> TestT m a
catchError TestT m a
m e -> TestT m a
onErr =
    forall (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall a b. (a -> b) -> a -> b
$
      (forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest TestT m a
m) forall e (m :: * -> *) a.
MonadError e m =>
m a -> (e -> m a) -> m a
`catchError`
      (forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a.
TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> TestT m a
onErr)
instance MonadResource m => MonadResource (TestT m) where
  liftResourceT :: forall a. ResourceT IO a -> TestT m a
liftResourceT =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadResource m => ResourceT IO a -> m a
liftResourceT
instance MonadTransControl TestT where
  type StT TestT a =
    (Either Failure a, Journal)
  liftWith :: forall (m :: * -> *) a. Monad m => (Run TestT -> m a) -> TestT m a
liftWith Run TestT -> m a
f =
    forall (m :: * -> *) a. m (Either Failure a, Journal) -> TestT m a
mkTestT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (, forall a. Monoid a => a
mempty) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ Run TestT -> m a
f forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. TestT m a -> m (Either Failure a, Journal)
runTestT
  restoreT :: forall (m :: * -> *) a. Monad m => m (StT TestT a) -> TestT m a
restoreT =
    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 :: forall a. (RunInBase (TestT m) b -> b a) -> TestT m a
liftBaseWith =
    forall (t :: (* -> *) -> * -> *) (b :: * -> *) (m :: * -> *) a.
(MonadTransControl t, MonadBaseControl b m) =>
(RunInBaseDefault t m b -> b a) -> t m a
defaultLiftBaseWith
  restoreM :: forall a. StM (TestT m) a -> TestT m a
restoreM =
    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 :: forall a. Test a -> TestT m a
liftTest =
    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 (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Identity a -> a
runIdentity)
instance MonadTest m => MonadTest (IdentityT m) where
  liftTest :: forall a. Test a -> IdentityT m a
liftTest =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest
instance MonadTest m => MonadTest (MaybeT m) where
  liftTest :: forall a. Test a -> MaybeT m a
liftTest =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest
instance MonadTest m => MonadTest (ExceptT x m) where
  liftTest :: forall a. Test a -> ExceptT x m a
liftTest =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest
instance MonadTest m => MonadTest (ReaderT r m) where
  liftTest :: forall a. Test a -> ReaderT r m a
liftTest =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest
instance MonadTest m => MonadTest (Lazy.StateT s m) where
  liftTest :: forall a. Test a -> StateT s m a
liftTest =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest
instance MonadTest m => MonadTest (Strict.StateT s m) where
  liftTest :: forall a. Test a -> StateT s m a
liftTest =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest
instance (MonadTest m, Monoid w) => MonadTest (Lazy.WriterT w m) where
  liftTest :: forall a. Test a -> WriterT w m a
liftTest =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest
instance (MonadTest m, Monoid w) => MonadTest (Strict.WriterT w m) where
  liftTest :: forall a. Test a -> WriterT w m a
liftTest =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest
instance (MonadTest m, Monoid w) => MonadTest (Lazy.RWST r w s m) where
  liftTest :: forall a. Test a -> RWST r w s m a
liftTest =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest
instance (MonadTest m, Monoid w) => MonadTest (Strict.RWST r w s m) where
  liftTest :: forall a. Test a -> RWST r w s m a
liftTest =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest
instance MonadTest m => MonadTest (ContT r m) where
  liftTest :: forall a. Test a -> ContT r m a
liftTest =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest
instance MonadTest m => MonadTest (ResourceT m) where
  liftTest :: forall a. Test a -> ResourceT m a
liftTest =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest
mkTestT :: m (Either Failure a, Journal) -> TestT m a
mkTestT :: forall (m :: * -> *) a. m (Either Failure a, Journal) -> TestT m a
mkTestT =
  forall (m :: * -> *) a.
ExceptT Failure (WriterT Journal m) a -> TestT m a
TestT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Lazy.WriterT
mkTest :: (Either Failure a, Journal) -> Test a
mkTest :: forall a. (Either Failure a, Journal) -> Test a
mkTest =
  forall (m :: * -> *) a. m (Either Failure a, Journal) -> TestT m a
mkTestT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Identity a
Identity
runTestT :: TestT m a -> m (Either Failure a, Journal)
runTestT :: forall (m :: * -> *) a. TestT m a -> m (Either Failure a, Journal)
runTestT =
  forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
Lazy.runWriterT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a.
TestT m a -> ExceptT Failure (WriterT Journal m) a
unTest
runTest :: Test a -> (Either Failure a, Journal)
runTest :: forall a. Test a -> (Either Failure a, Journal)
runTest =
  forall a. Identity a -> a
runIdentity forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. TestT m a -> m (Either Failure a, Journal)
runTestT
writeLog :: MonadTest m => Log -> m ()
writeLog :: forall (m :: * -> *). MonadTest m => Log -> m ()
writeLog Log
x =
  forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest forall a b. (a -> b) -> a -> b
$ forall a. (Either Failure a, Journal) -> Test a
mkTest (forall (f :: * -> *) a. Applicative f => a -> f a
pure (), ([Log] -> Journal
Journal [Log
x]))
failWith :: (MonadTest m, HasCallStack) => Maybe Diff -> String -> m a
failWith :: forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith Maybe Diff
mdiff String
msg =
  forall (m :: * -> *) a. MonadTest m => Test a -> m a
liftTest forall a b. (a -> b) -> a -> b
$ forall a. (Either Failure a, Journal) -> Test a
mkTest (forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Maybe Span -> String -> Maybe Diff -> Failure
Failure (CallStack -> Maybe Span
getCaller HasCallStack => CallStack
callStack) String
msg Maybe Diff
mdiff, forall a. Monoid a => a
mempty)
annotate :: (MonadTest m, HasCallStack) => String -> m ()
annotate :: forall (m :: * -> *). (MonadTest m, HasCallStack) => String -> m ()
annotate String
x = do
  forall (m :: * -> *). MonadTest m => Log -> m ()
writeLog forall a b. (a -> b) -> a -> b
$ Maybe Span -> String -> Log
Annotation (CallStack -> Maybe Span
getCaller HasCallStack => CallStack
callStack) String
x
annotateShow :: (MonadTest m, Show a, HasCallStack) => a -> m ()
annotateShow :: forall (m :: * -> *) a.
(MonadTest m, Show a, HasCallStack) =>
a -> m ()
annotateShow a
x = do
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). (MonadTest m, HasCallStack) => String -> m ()
annotate (forall a. Show a => a -> String
showPretty a
x)
footnote :: MonadTest m => String -> m ()
 =
  forall (m :: * -> *). MonadTest m => Log -> m ()
writeLog forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Log
Footnote
footnoteShow :: (MonadTest m, Show a) => a -> m ()
 =
  forall (m :: * -> *). MonadTest m => Log -> m ()
writeLog forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Log
Footnote forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
showPretty
failDiff :: (MonadTest m, Show a, Show b, HasCallStack) => a -> b -> m ()
failDiff :: forall (m :: * -> *) a b.
(MonadTest m, Show a, Show b, HasCallStack) =>
a -> b -> m ()
failDiff a
x b
y =
  case Value -> Value -> ValueDiff
valueDiff forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Show a => a -> Maybe Value
mkValue a
x forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Show a => a -> Maybe Value
mkValue b
y of
    Maybe ValueDiff
Nothing ->
      forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$
        forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith forall a. Maybe a
Nothing forall a b. (a -> b) -> a -> b
$
        [String] -> String
unlines forall a b. (a -> b) -> a -> b
$ [
            String
"Failed"
          , String
"━━ lhs ━━"
          , forall a. Show a => a -> String
showPretty a
x
          , String
"━━ rhs ━━"
          , forall a. Show a => a -> String
showPretty b
y
          ]
    Just vdiff :: ValueDiff
vdiff@(ValueSame Value
_) ->
      forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$
        forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith (forall a. a -> Maybe a
Just 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 ->
      forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$
        forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith (forall a. a -> Maybe a
Just 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
""
failException :: (MonadTest m, HasCallStack) => SomeException -> m a
failException :: forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
SomeException -> m a
failException SomeException
x =
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$
    forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
[String] -> SomeException -> m a
failExceptionWith [] SomeException
x
failExceptionWith :: (MonadTest m, HasCallStack) => [String] -> SomeException -> m a
failExceptionWith :: forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
[String] -> SomeException -> m a
failExceptionWith [String]
messages (SomeException e
x) =
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack
    forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith forall a. Maybe a
Nothing forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines forall a b. (a -> b) -> a -> b
$ [String]
messages forall a. Semigroup a => a -> a -> a
<> [
        String
"━━━ Exception (" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall a. Typeable a => a -> TypeRep
typeOf e
x) forall a. [a] -> [a] -> [a]
++ String
") ━━━"
      , forall a. (a -> Bool) -> [a] -> [a]
List.dropWhileEnd Char -> Bool
Char.isSpace (forall e. Exception e => e -> String
displayException e
x)
      ]
failure :: (MonadTest m, HasCallStack) => m a
failure :: forall (m :: * -> *) a. (MonadTest m, HasCallStack) => m a
failure =
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith forall a. Maybe a
Nothing String
""
success :: MonadTest m => m ()
success :: forall (m :: * -> *). MonadTest m => m ()
success =
  forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
assert :: (MonadTest m, HasCallStack) => Bool -> m ()
assert :: forall (m :: * -> *). (MonadTest m, HasCallStack) => Bool -> m ()
assert Bool
b = do
  Bool
ok <- forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. (MonadTest m, HasCallStack) => a -> m a
eval Bool
b
  if Bool
ok then
    forall (m :: * -> *). MonadTest m => m ()
success
  else
    forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall (m :: * -> *) a. (MonadTest m, HasCallStack) => m a
failure
diff :: (MonadTest m, Show a, Show b, HasCallStack) => a -> (a -> b -> Bool) -> b -> m ()
diff :: forall (m :: * -> *) a b.
(MonadTest m, Show a, Show b, HasCallStack) =>
a -> (a -> b -> Bool) -> b -> m ()
diff a
x a -> b -> Bool
op b
y = do
  Bool
ok <- forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. (MonadTest m, HasCallStack) => a -> m a
eval (a
x a -> b -> Bool
`op` b
y)
  if Bool
ok then
    forall (m :: * -> *). MonadTest m => m ()
success
  else
    forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
(MonadTest m, Show a, Show b, HasCallStack) =>
a -> b -> m ()
failDiff a
x b
y
infix 4 ===
(===) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m ()
=== :: forall (m :: * -> *) a.
(MonadTest m, Eq a, Show a, HasCallStack) =>
a -> a -> m ()
(===) a
x a
y =
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$
    forall (m :: * -> *) a b.
(MonadTest m, Show a, Show b, HasCallStack) =>
a -> (a -> b -> Bool) -> b -> m ()
diff a
x forall a. Eq a => a -> a -> Bool
(==) a
y
infix 4 /==
(/==) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m ()
/== :: forall (m :: * -> *) a.
(MonadTest m, Eq a, Show a, HasCallStack) =>
a -> a -> m ()
(/==) a
x a
y =
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$
    forall (m :: * -> *) a b.
(MonadTest m, Show a, Show b, HasCallStack) =>
a -> (a -> b -> Bool) -> b -> m ()
diff a
x forall a. Eq a => a -> a -> Bool
(/=) a
y
eval :: (MonadTest m, HasCallStack) => a -> m a
eval :: forall (m :: * -> *) a. (MonadTest m, HasCallStack) => a -> m a
eval a
x =
  forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
SomeException -> m a
failException) forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Either SomeException a
tryEvaluate a
x)
evalNF :: (MonadTest m, NFData a, HasCallStack) => a -> m a
evalNF :: forall (m :: * -> *) a.
(MonadTest m, NFData a, HasCallStack) =>
a -> m a
evalNF a
x =
  let
    messages :: [String]
messages =
      [String
"━━━ Value could not be evaluated to normal form ━━━"]
  in
    forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
[String] -> SomeException -> m a
failExceptionWith [String]
messages)) forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Either SomeException a
tryEvaluate (forall a. NFData a => a -> ()
rnf a
x)) forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> a
x
evalM :: (MonadTest m, MonadCatch m, HasCallStack) => m a -> m a
evalM :: forall (m :: * -> *) a.
(MonadTest m, MonadCatch m, HasCallStack) =>
m a -> m a
evalM m a
m =
  forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
SomeException -> m a
failException) forall (f :: * -> *) a. Applicative f => a -> f a
pure forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (m :: * -> *) a.
MonadCatch m =>
m a -> m (Either SomeException a)
tryAll m a
m
evalIO :: (MonadTest m, MonadIO m, HasCallStack) => IO a -> m a
evalIO :: forall (m :: * -> *) a.
(MonadTest m, MonadIO m, HasCallStack) =>
IO a -> m a
evalIO IO a
m =
  forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
SomeException -> m a
failException) forall (f :: * -> *) a. Applicative f => a -> f a
pure forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (forall (m :: * -> *) a.
MonadCatch m =>
m a -> m (Either SomeException a)
tryAll IO a
m)
evalEither :: (MonadTest m, Show x, HasCallStack) => Either x a -> m a
evalEither :: forall (m :: * -> *) x a.
(MonadTest m, Show x, HasCallStack) =>
Either x a -> m a
evalEither = \case
  Left x
x ->
    forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith forall a. Maybe a
Nothing forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
showPretty x
x
  Right a
x ->
    forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x
evalEitherM :: (MonadTest m, Show x, MonadCatch m, HasCallStack) => m (Either x a) -> m a
evalEitherM :: forall (m :: * -> *) x a.
(MonadTest m, Show x, MonadCatch m, HasCallStack) =>
m (Either x a) -> m a
evalEitherM =
  forall (m :: * -> *) x a.
(MonadTest m, Show x, HasCallStack) =>
Either x a -> m a
evalEither forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< forall (m :: * -> *) a.
(MonadTest m, MonadCatch m, HasCallStack) =>
m a -> m a
evalM
evalExceptT :: (MonadTest m, Show x, HasCallStack) => ExceptT x m a -> m a
evalExceptT :: forall (m :: * -> *) x a.
(MonadTest m, Show x, HasCallStack) =>
ExceptT x m a -> m a
evalExceptT ExceptT x m a
m =
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall (m :: * -> *) x a.
(MonadTest m, Show x, HasCallStack) =>
Either x a -> m a
evalEither forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT x m a
m
evalMaybe :: (MonadTest m, Show a, HasCallStack) => Maybe a -> m a
evalMaybe :: forall (m :: * -> *) a.
(MonadTest m, Show a, HasCallStack) =>
Maybe a -> m a
evalMaybe = \case
  Maybe a
Nothing ->
    forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
(MonadTest m, HasCallStack) =>
Maybe Diff -> String -> m a
failWith forall a. Maybe a
Nothing String
"the value was Nothing"
  Just a
x ->
    forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x
evalMaybeM :: (MonadTest m, Show a, MonadCatch m, HasCallStack) => m (Maybe a) -> m a
evalMaybeM :: forall (m :: * -> *) a.
(MonadTest m, Show a, MonadCatch m, HasCallStack) =>
m (Maybe a) -> m a
evalMaybeM =
  forall (m :: * -> *) a.
(MonadTest m, Show a, HasCallStack) =>
Maybe a -> m a
evalMaybe forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< forall (m :: * -> *) a.
(MonadTest m, MonadCatch m, HasCallStack) =>
m a -> m a
evalM
instance MonadTrans PropertyT where
  lift :: forall (m :: * -> *) a. Monad m => m a -> PropertyT m a
lift =
    forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift
instance Monad m => MonadFail (PropertyT m) where
  fail :: forall a. String -> PropertyT m a
fail String
err =
    forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT (forall (m :: * -> *) a. MonadFail m => String -> m a
Fail.fail String
err)
instance MFunctor PropertyT where
  hoist :: forall (m :: * -> *) (n :: * -> *) b.
Monad m =>
(forall a. m a -> n a) -> PropertyT m b -> PropertyT n b
hoist forall a. m a -> n a
f =
    forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 {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) forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 :: forall (f :: (* -> *) -> * -> *) (m :: * -> *) a.
Transformer f PropertyT m =>
PropertyT (f m) a -> f (PropertyT m) a
distributeT =
    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 (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    forall (g :: (* -> *) -> * -> *) (f :: (* -> *) -> * -> *)
       (m :: * -> *) a.
(MonadTransDistributive g, Transformer f g m) =>
g (f m) a -> f (g m) a
distributeT forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    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 (g :: (* -> *) -> * -> *) (f :: (* -> *) -> * -> *)
       (m :: * -> *) a.
(MonadTransDistributive g, Transformer f g m) =>
g (f m) a -> f (g m) a
distributeT forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    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 :: forall a.
(State# (PrimState (PropertyT m))
 -> (# State# (PrimState (PropertyT m)), a #))
-> PropertyT m a
primitive =
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive
instance Monad m => MonadTest (PropertyT m) where
  liftTest :: forall a. Test a -> PropertyT m a
liftTest =
    forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Identity a -> a
runIdentity)
instance MonadPlus m => MonadPlus (PropertyT m) where
  mzero :: forall a. PropertyT m a
mzero =
    forall (m :: * -> *) a. Monad m => PropertyT m a
discard
  mplus :: forall a. PropertyT m a -> PropertyT m a -> PropertyT m a
mplus (PropertyT TestT (GenT m) a
x) (PropertyT TestT (GenT m) a
y) =
    forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. m (Either Failure a, Journal) -> TestT m a
mkTestT forall a b. (a -> b) -> a -> b
$
      forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus (forall (m :: * -> *) a. TestT m a -> m (Either Failure a, Journal)
runTestT TestT (GenT m) a
x) (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 :: forall a. PropertyT m a
empty =
    forall (m :: * -> *) a. MonadPlus m => m a
mzero
  <|> :: forall a. PropertyT m a -> PropertyT m a -> PropertyT m a
(<|>) =
    forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus
forAllWithT :: (Monad m, HasCallStack) => (a -> String) -> GenT m a -> PropertyT m a
forAllWithT :: forall (m :: * -> *) a.
(Monad m, HasCallStack) =>
(a -> String) -> GenT m a -> PropertyT m a
forAllWithT a -> String
render GenT m a
gen = do
  a
x <- forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift GenT m a
gen
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). (MonadTest m, HasCallStack) => String -> m ()
annotate (a -> String
render a
x)
  return a
x
forAllWith :: (Monad m, HasCallStack) => (a -> String) -> Gen a -> PropertyT m a
forAllWith :: forall (m :: * -> *) a.
(Monad m, HasCallStack) =>
(a -> String) -> Gen a -> PropertyT m a
forAllWith a -> String
render Gen a
gen =
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
(Monad m, HasCallStack) =>
(a -> String) -> GenT m a -> PropertyT m a
forAllWithT a -> String
render forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => Gen a -> GenT m a
Gen.generalize Gen a
gen
forAllT :: (Monad m, Show a, HasCallStack) => GenT m a -> PropertyT m a
forAllT :: forall (m :: * -> *) a.
(Monad m, Show a, HasCallStack) =>
GenT m a -> PropertyT m a
forAllT GenT m a
gen =
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
(Monad m, HasCallStack) =>
(a -> String) -> GenT m a -> PropertyT m a
forAllWithT forall a. Show a => a -> String
showPretty GenT m a
gen
forAll :: (Monad m, Show a, HasCallStack) => Gen a -> PropertyT m a
forAll :: forall (m :: * -> *) a.
(Monad m, Show a, HasCallStack) =>
Gen a -> PropertyT m a
forAll Gen a
gen =
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
(Monad m, HasCallStack) =>
(a -> String) -> Gen a -> PropertyT m a
forAllWith forall a. Show a => a -> String
showPretty Gen a
gen
discard :: Monad m => PropertyT m a
discard :: forall (m :: * -> *) a. Monad m => PropertyT m a
discard =
  forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (forall (m :: * -> *) a. Monad m => Gen a -> GenT m a
Gen.generalize forall (m :: * -> *) a. MonadGen m => m a
Gen.discard)
test :: Monad m => TestT m a -> PropertyT m a
test :: forall (m :: * -> *) a. Monad m => TestT m a -> PropertyT m a
test =
  forall (m :: * -> *) a. TestT (GenT m) a -> PropertyT m a
PropertyT forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift
defaultConfig :: PropertyConfig
defaultConfig :: PropertyConfig
defaultConfig =
  PropertyConfig {
      propertyDiscardLimit :: DiscardLimit
propertyDiscardLimit =
        DiscardLimit
100
    , propertyShrinkLimit :: ShrinkLimit
propertyShrinkLimit =
        ShrinkLimit
1000
    , propertyShrinkRetries :: ShrinkRetries
propertyShrinkRetries =
        ShrinkRetries
0
    , propertyTerminationCriteria :: TerminationCriteria
propertyTerminationCriteria =
        TestLimit -> TerminationCriteria
NoConfidenceTermination TestLimit
defaultMinTests
    , propertySkip :: Maybe Skip
propertySkip =
        forall a. Maybe a
Nothing
    }
defaultMinTests :: TestLimit
defaultMinTests :: TestLimit
defaultMinTests = TestLimit
100
defaultConfidence :: Confidence
defaultConfidence :: Confidence
defaultConfidence = Confidence
10 forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
9 :: Int)
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
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 forall a b. (a -> b) -> a -> b
$ \config :: PropertyConfig
config@PropertyConfig{Maybe Skip
TerminationCriteria
ShrinkRetries
ShrinkLimit
DiscardLimit
propertySkip :: Maybe Skip
propertyTerminationCriteria :: TerminationCriteria
propertyShrinkRetries :: ShrinkRetries
propertyShrinkLimit :: ShrinkLimit
propertyDiscardLimit :: DiscardLimit
propertySkip :: PropertyConfig -> Maybe Skip
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 forall a b. (a -> b) -> a -> b
$ \config :: PropertyConfig
config@PropertyConfig{Maybe Skip
TerminationCriteria
ShrinkRetries
ShrinkLimit
DiscardLimit
propertySkip :: Maybe Skip
propertyTerminationCriteria :: TerminationCriteria
propertyShrinkRetries :: ShrinkRetries
propertyShrinkLimit :: ShrinkLimit
propertyDiscardLimit :: DiscardLimit
propertySkip :: PropertyConfig -> Maybe Skip
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 }
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 forall a b. (a -> b) -> a -> b
$ \config :: PropertyConfig
config@PropertyConfig{Maybe Skip
TerminationCriteria
ShrinkRetries
ShrinkLimit
DiscardLimit
propertySkip :: Maybe Skip
propertyTerminationCriteria :: TerminationCriteria
propertyShrinkRetries :: ShrinkRetries
propertyShrinkLimit :: ShrinkLimit
propertyDiscardLimit :: DiscardLimit
propertySkip :: PropertyConfig -> Maybe Skip
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 }
withDiscards :: DiscardLimit -> Property -> Property
withDiscards :: DiscardLimit -> Property -> Property
withDiscards DiscardLimit
n =
  (PropertyConfig -> PropertyConfig) -> Property -> Property
mapConfig forall a b. (a -> b) -> a -> b
$ \PropertyConfig
config -> PropertyConfig
config { propertyDiscardLimit :: DiscardLimit
propertyDiscardLimit = DiscardLimit
n }
withShrinks :: ShrinkLimit -> Property -> Property
withShrinks :: ShrinkLimit -> Property -> Property
withShrinks ShrinkLimit
n =
  (PropertyConfig -> PropertyConfig) -> Property -> Property
mapConfig forall a b. (a -> b) -> a -> b
$ \PropertyConfig
config -> PropertyConfig
config { propertyShrinkLimit :: ShrinkLimit
propertyShrinkLimit = ShrinkLimit
n }
withRetries :: ShrinkRetries -> Property -> Property
withRetries :: ShrinkRetries -> Property -> Property
withRetries ShrinkRetries
n =
  (PropertyConfig -> PropertyConfig) -> Property -> Property
mapConfig forall a b. (a -> b) -> a -> b
$ \PropertyConfig
config -> PropertyConfig
config { propertyShrinkRetries :: ShrinkRetries
propertyShrinkRetries = ShrinkRetries
n }
withSkip :: Skip -> Property -> Property
withSkip :: Skip -> Property -> Property
withSkip Skip
s =
  (PropertyConfig -> PropertyConfig) -> Property -> Property
mapConfig forall a b. (a -> b) -> a -> b
$ \PropertyConfig
config -> PropertyConfig
config { propertySkip :: Maybe Skip
propertySkip = forall a. a -> Maybe a
Just Skip
s }
property :: HasCallStack => PropertyT IO () -> Property
property :: HasCallStack => PropertyT IO () -> Property
property PropertyT IO ()
m =
  PropertyConfig -> PropertyT IO () -> Property
Property PropertyConfig
defaultConfig forall a b. (a -> b) -> a -> b
$
    forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (forall (m :: * -> *) a.
(MonadTest m, MonadCatch m, HasCallStack) =>
m a -> m a
evalM PropertyT IO ()
m)
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 =
    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 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 =
    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
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) =
    forall a.
LabelName -> Maybe Span -> CoverPercentage -> a -> Label a
MkLabel LabelName
name Maybe Span
location CoverPercentage
percentage (a
m0 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) =
    forall a. Map LabelName (Label a) -> Coverage a
Coverage forall a b. (a -> b) -> a -> b
$
      forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
Map.foldrWithKey (forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.insertWith 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 =
    forall a. Map LabelName (Label a) -> Coverage a
Coverage forall a. Monoid a => a
mempty
  mappend :: Coverage a -> Coverage a -> Coverage a
mappend =
    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 =
      forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
count forall a. Fractional a => a -> a -> a
/ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
tests forall a. Num a => a -> a -> a
* Double
100
    thousandths :: Int
    thousandths :: Int
thousandths =
      forall a b. (RealFrac a, Integral b) => a -> b
round forall a b. (a -> b) -> a -> b
$ Double
percentage forall a. Num a => a -> a -> a
* Double
10
  in
    Double -> CoverPercentage
CoverPercentage (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
thousandths 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 forall a. Ord a => a -> a -> Bool
>= CoverPercentage
minimum_
coverageSuccess :: TestCount -> Coverage CoverCount -> Bool
coverageSuccess :: TestCount -> Coverage CoverCount -> Bool
coverageSuccess TestCount
tests =
  forall (t :: * -> *) a. Foldable t => t a -> Bool
null 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) =
  forall a. (a -> Bool) -> [a] -> [a]
List.filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestCount -> Label CoverCount -> Bool
labelCovered TestCount
tests) (forall k a. Map k a -> [a]
Map.elems Map LabelName (Label CoverCount)
kvs)
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
..} =
      forall a b. (a, b) -> a
fst (TestCount -> Confidence -> Label CoverCount -> (Double, Double)
boundsForLabel TestCount
tests Confidence
confidence Label CoverCount
coverCount)
        forall a. Ord a => a -> a -> Bool
>= CoverPercentage -> Double
unCoverPercentage CoverPercentage
labelMinimum forall a. Fractional a => a -> a -> a
/ Double
100.0
  in
    forall (t :: * -> *). Foldable t => t Bool -> Bool
and forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Label CoverCount -> Bool
assertLow forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [a]
Map.elems forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Coverage a -> Map LabelName (Label a)
coverageLabels
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
..} =
      forall a b. (a, b) -> b
snd (TestCount -> Confidence -> Label CoverCount -> (Double, Double)
boundsForLabel TestCount
tests Confidence
confidence Label CoverCount
coverCount)
        forall a. Ord a => a -> a -> Bool
< (CoverPercentage -> Double
unCoverPercentage CoverPercentage
labelMinimum forall a. Fractional a => a -> a -> a
/ Double
100.0)
  in
    forall (t :: * -> *). Foldable t => t Bool -> Bool
or forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Label CoverCount -> Bool
assertHigh forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [a]
Map.elems forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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
    (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ CoverCount -> Int
unCoverCount CoverCount
labelAnnotation)
    (forall a b. (Integral a, Num b) => a -> b
fromIntegral TestCount
tests)
    (Double
1 forall a. Fractional a => a -> a -> a
/ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Confidence -> Int64
unConfidence Confidence
confidence))
wilsonBounds :: Integer -> Integer -> Double -> (Double, Double)
wilsonBounds :: Integer -> Integer -> Double -> (Double, Double)
wilsonBounds Integer
positives Integer
count Double
acceptance =
  let
    p :: Double
p =
      forall a. Fractional a => Rational -> a
fromRational forall a b. (a -> b) -> a -> b
$ Integer
positives forall a. Integral a => a -> a -> Ratio a
% Integer
count
    n :: Double
n =
      forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
count
    z :: Double
z =
      forall a. InvErf a => a -> a
invnormcdf forall a b. (a -> b) -> a -> b
$ Double
1 forall a. Num a => a -> a -> a
- Double
acceptance forall a. Fractional a => a -> a -> a
/ Double
2
    midpoint :: Double
midpoint =
      Double
p forall a. Num a => a -> a -> a
+ Double
z forall a. Num a => a -> a -> a
* Double
z forall a. Fractional a => a -> a -> a
/ (Double
2 forall a. Num a => a -> a -> a
* Double
n)
    offset :: Double
offset =
      Double
z forall a. Fractional a => a -> a -> a
/ (Double
1 forall a. Num a => a -> a -> a
+ Double
z forall a. Floating a => a -> a -> a
** Double
2 forall a. Fractional a => a -> a -> a
/ Double
n) forall a. Num a => a -> a -> a
* forall a. Floating a => a -> a
sqrt (Double
p forall a. Num a => a -> a -> a
* (Double
1 forall a. Num a => a -> a -> a
- Double
p) forall a. Fractional a => a -> a -> a
/ Double
n forall a. Num a => a -> a -> a
+ Double
z forall a. Floating a => a -> a -> a
** Double
2 forall a. Fractional a => a -> a -> a
/ (Double
4 forall a. Num a => a -> a -> a
* Double
n forall a. Floating a => a -> a -> a
** Double
2))
    denominator :: Double
denominator =
      Double
1 forall a. Num a => a -> a -> a
+ Double
z forall a. Num a => a -> a -> a
* Double
z forall a. Fractional a => a -> a -> a
/ Double
n
    low :: Double
low =
      (Double
midpoint forall a. Num a => a -> a -> a
- Double
offset) forall a. Fractional a => a -> a -> a
/ Double
denominator
    high :: Double
high =
      (Double
midpoint forall a. Num a => a -> a -> a
+ Double
offset) forall a. Fractional a => a -> a -> a
/ Double
denominator
  in
    (Double
low, Double
high)
fromLabel :: Label a -> Coverage a
fromLabel :: forall a. Label a -> Coverage a
fromLabel Label a
x =
  forall a. Map LabelName (Label a) -> Coverage a
Coverage forall a b. (a -> b) -> a -> b
$
    forall k a. k -> a -> Map k a
Map.singleton (forall a. Label a -> LabelName
labelName Label a
x) Label a
x
unionsCoverage :: Semigroup a => [Coverage a] -> Coverage a
unionsCoverage :: forall a. Semigroup a => [Coverage a] -> Coverage a
unionsCoverage =
  forall a. Map LabelName (Label a) -> Coverage a
Coverage forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
(a -> a -> a) -> f (Map k a) -> Map k a
Map.unionsWith forall a. Semigroup a => a -> a -> a
(<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Coverage a -> Map LabelName (Label a)
coverageLabels
journalCoverage :: Journal -> Coverage CoverCount
journalCoverage :: Journal -> Coverage CoverCount
journalCoverage (Journal [Log]
logs) =
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Cover -> CoverCount
toCoverCount forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  forall a. Semigroup a => [Coverage a] -> Coverage a
unionsCoverage forall a b. (a -> b) -> a -> b
$ do
    Label Label Cover
x <- [Log]
logs
    forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Label a -> Coverage a
fromLabel Label Cover
x)
cover :: (MonadTest m, HasCallStack) => CoverPercentage -> LabelName -> Bool -> m ()
cover :: forall (m :: * -> *).
(MonadTest m, HasCallStack) =>
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
    forall (m :: * -> *). MonadTest m => Log -> m ()
writeLog forall b c a. (b -> c) -> (a -> b) -> a -> c
. Label Cover -> Log
Label forall a b. (a -> b) -> a -> b
$
      forall a.
LabelName -> Maybe Span -> CoverPercentage -> a -> Label a
MkLabel LabelName
name (CallStack -> Maybe Span
getCaller HasCallStack => CallStack
callStack) CoverPercentage
minimum_ Cover
cover_
classify :: (MonadTest m, HasCallStack) => LabelName -> Bool -> m ()
classify :: forall (m :: * -> *).
(MonadTest m, HasCallStack) =>
LabelName -> Bool -> m ()
classify LabelName
name Bool
covered =
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$
    forall (m :: * -> *).
(MonadTest m, HasCallStack) =>
CoverPercentage -> LabelName -> Bool -> m ()
cover CoverPercentage
0 LabelName
name Bool
covered
label :: (MonadTest m, HasCallStack) => LabelName -> m ()
label :: forall (m :: * -> *).
(MonadTest m, HasCallStack) =>
LabelName -> m ()
label LabelName
name =
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$
    forall (m :: * -> *).
(MonadTest m, HasCallStack) =>
CoverPercentage -> LabelName -> Bool -> m ()
cover CoverPercentage
0 LabelName
name Bool
True
collect :: (MonadTest m, Show a, HasCallStack) => a -> m ()
collect :: forall (m :: * -> *) a.
(MonadTest m, Show a, HasCallStack) =>
a -> m ()
collect a
x =
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$
    forall (m :: * -> *).
(MonadTest m, HasCallStack) =>
CoverPercentage -> LabelName -> Bool -> m ()
cover CoverPercentage
0 (String -> LabelName
LabelName (forall a. Show a => a -> String
show a
x)) Bool
True