cleveland-0.3.1: Testing framework for Morley.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Cleveland.Util

Description

Testing utility functions used by testing framework itself or intended to be used by test writers.

Synopsis

Documentation

leftToShowPanic :: (PrettyShow e, Show e, HasCallStack) => Either e a -> a Source #

(?-) :: Text -> a -> (Text, a) infixr 0 Source #

Make a tuple with name without extra syntactic noise.

Property

failedTest :: (HasCallStack, MonadTest m) => Text -> m () Source #

A Property that always fails with given message.

succeededTest :: MonadTest m => m () Source #

A Property that always succeeds.

eitherIsLeft :: (Show b, MonadTest m, HasCallStack) => Either a b -> m () Source #

The Property holds on `Left a`.

eitherIsRight :: (Show a, MonadTest m, HasCallStack) => Either a b -> m () Source #

The Property holds on `Right b`.

meanTimeUpperBoundProp :: (KnownDivRat unit Second, KnownUnitName unit, HasCallStack) => Time unit -> (a -> b) -> a -> Property Source #

Benchmarks the given function and checks that the mean time to evaluate to weak head normal form is under the given amount of time.

This test fails if the benchmark takes longer than 30 seconds to run.

meanTimeUpperBoundPropNF :: (KnownDivRat unit Second, KnownUnitName unit, HasCallStack, NFData b) => Time unit -> (a -> b) -> a -> Property Source #

Benchmarks the given function and checks that the mean time to evaluate to normal form is under the given amount of time.

This test aborts and fails if the benchmark takes longer than 120 seconds to run.

Generator

genTuple2 :: MonadGen m => m a -> m b -> m (a, b) Source #

Generates an a and a b and wraps them in a tuple.

genRandom :: MonadGen m => (forall n. MonadRandom n => n a) -> m a Source #

Construct a hedgehog generator from a generator relying on MonadRandom.

This neither shrinks nor generates values in a reasonable order, use only when such properties are justified for your type.

runGen :: HasCallStack => Size -> Word64 -> Gen a -> a Source #

Run the given generator deterministically, by fixing its size and seed.

Roundtrip

roundtripTree :: forall x y err. (Show x, Show y, Show err, Typeable x, Eq x, Eq err, HasCallStack) => Gen x -> (x -> y) -> (y -> Either err x) -> TestTree Source #

This TestTree contains a property based test for conversion from some x to some y and back to x (it should successfully return the initial x).

assertGoesBefore :: forall d1 d2. (DocItem d1, DocItem d2) => Proxy d1 -> Proxy d2 -> Assertion Source #

Test that one doc item goes before another doc item in generated documentation.

goesBefore :: forall d1 d2. (DocItem d1, DocItem d2) => Proxy d1 -> Proxy d2 -> TestTree Source #

Test that one doc item goes before another doc item in generated documentation.

Pretty-printing

formatValue :: forall t. SingI t => Value t -> Builder Source #

formatSomeValue :: (forall t. c t => SingI t) => SomeConstrainedValue c -> Builder Source #

data ShowWith a Source #

Derive a Show instance for a type using a custom "show" function. Note: the shown value is paren-wrapped iff it's a subexpression, just as an ordinary Show would do.

Constructors

ShowWith (a -> String) a 

Instances

Instances details
Show (ShowWith a) Source # 
Instance details

Defined in Test.Cleveland.Util

Methods

showsPrec :: Int -> ShowWith a -> ShowS #

show :: ShowWith a -> String #

showList :: [ShowWith a] -> ShowS #

Eq a => Eq (ShowWith a) Source # 
Instance details

Defined in Test.Cleveland.Util

Methods

(==) :: ShowWith a -> ShowWith a -> Bool #

(/=) :: ShowWith a -> ShowWith a -> Bool #

newtype Showing a Source #

Derive a Buildable instance for a type using show.

Constructors

Showing a 

Instances

Instances details
Show a => Show (Showing a) Source # 
Instance details

Defined in Test.Cleveland.Util

Methods

showsPrec :: Int -> Showing a -> ShowS #

show :: Showing a -> String #

showList :: [Showing a] -> ShowS #

Show a => Buildable (Showing a) Source # 
Instance details

Defined in Test.Cleveland.Util

Methods

build :: Showing a -> Builder #

Eq a => Eq (Showing a) Source # 
Instance details

Defined in Test.Cleveland.Util

Methods

(==) :: Showing a -> Showing a -> Bool #

(/=) :: Showing a -> Showing a -> Bool #

Time

ceilingUnit :: forall (unit :: Rat). Time unit -> Time unit Source #

Round the given time to the nearest whole number of the given unit, not smaller than the given time.

ceilingUnit (sec 2.0) == sec 2
ceilingUnit (sec 2.1) == sec 3
ceilingUnit (sec 2.9) == sec 3

timeToFixed :: forall precision unit. HasResolution precision => Time unit -> Fixed precision Source #

Converts the given time to a number with fixed-precision (in the given time unit).

timeToFixed (sec 1.234) == (1.2            :: Deci)
timeToFixed (sec 1.234) == (1.234          :: Milli)
timeToFixed (sec 1.234) == (1.234000000000 :: Pico)

timeToNominalDiffTime :: KnownDivRat unit Second => Time unit -> NominalDiffTime Source #

Converts the given time to a NominalDiffTime.

Bytes

Traversals

mapEach :: (Each s t a b, Applicative m) => (a -> m b) -> s -> m t Source #

Version of mapM generalized with each.

Example:

(addr1, addr2, addr3) <- mapEach newAddress ("test1", "test2", "test3")

This is more type-safe than simple mapM since lists do not remember their length in types.

forEach :: (Each s t a b, Applicative m) => s -> (a -> m b) -> m t Source #

Version of mapEach with arguments flipped.

Re-exports

These functions from Time are re-exported here to make it convenient to call meanTimeUpperBoundProp and meanTimeUpperBoundPropNF.

mcs :: RatioNat -> Time Microsecond #

Creates Microsecond from given Natural.

>>> mcs 42
42mcs

ms :: RatioNat -> Time Millisecond #

Creates Millisecond from given Natural.

>>> ms 42
42ms

sec :: RatioNat -> Time Second #

Creates Second from given Natural.

>>> sec 42
42s

minute :: RatioNat -> Time Minute #

Creates Minute from given Natural.

>>> minute 42
42m