daytripper-0.3.1: Helpers for round-trip tests
Safe HaskellSafe-Inferred
LanguageGHC2021

Test.Daytripper

Synopsis

Documentation

class MonadFail m => MonadExpect m where Source #

Interface for asserting and performing IO in tests. TODO Migrate to MonadIO superclass when Falsify supports it.

Minimal complete definition

expectLiftIO, expectAssertEq, expectAssertFailure

Methods

expectLiftIO :: IO a -> m a Source #

expectAssertEq :: (Eq a, Show a) => a -> a -> m () Source #

expectAssertFailure :: String -> m () Source #

expectAssertBool :: String -> Bool -> m () Source #

Instances

Instances details
MonadExpect Property Source # 
Instance details

Defined in Test.Daytripper

MonadExpect IO Source # 
Instance details

Defined in Test.Daytripper

Methods

expectLiftIO :: IO a -> IO a Source #

expectAssertEq :: (Eq a, Show a) => a -> a -> IO () Source #

expectAssertFailure :: String -> IO () Source #

expectAssertBool :: String -> Bool -> IO () Source #

type Expect m a b c = Either b a -> m (b, m c) Source #

A general type of test expectation. Captures two stages of processing an input, first encoding, then decoding. The monad is typically something implementing MonadExpect, with assertions performed before returning values for further processing. The input is possibly missing, in which case we test decoding only.

expectBefore :: Monad m => (Maybe a -> m ()) -> Expect m a b c -> Expect m a b c Source #

Assert something before processing (before encoding and before decoding)

expectDuring :: Monad m => (Maybe a -> b -> m ()) -> Expect m a b c -> Expect m a b c Source #

Assert something during processing (after encoding and before decoding)

expectAfter :: Monad m => (Maybe a -> b -> c -> m ()) -> Expect m a b c -> Expect m a b c Source #

Asserting something after processing (after encoding and after decoding)

mkExpect :: MonadExpect m => (a -> m b) -> (b -> m c) -> (Maybe a -> c -> m ()) -> Expect m a b c Source #

A way of definining expectations from a pair of encode/decode functions and a comparison function.

runExpect :: Monad m => Expect m a b c -> a -> m c Source #

Simple way to run an expectation, ignoring the intermediate value.

data RT Source #

mkPropRT :: Show a => TestName -> Expect Property a b c -> Gen a -> RT Source #

Create a property-based roundtrip test

mkFileRT :: TestName -> Expect IO a ByteString c -> FilePath -> Maybe a -> RT Source #

Create a file-based ("golden") roundtrip test

mkUnitRT :: TestName -> Expect IO a b c -> a -> RT Source #

Create a unit roundtrip test

testRT :: RT -> TestTree Source #

Run a roundtrip test

newtype DaytripperWriteMissing Source #

By passing the appropriate arguments to Tasty (`--daytripper-write-missing` or `TASTY_DAYTRIPPER_WRITE_MISSING=True`) we can fill in the contents of missing files with the results of running tests.

daytripperIngredients :: [Ingredient] Source #

Tasty ingredients with write-missing support

daytripperMain :: TestTree -> IO () Source #

Tasty main with write-missing support