ImpSpec-0.1.0.0: Imperative approach to testing stateful applications. ImpSpec is build on top of HSpec and QuickCheck
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.ImpSpec

Synopsis

Documentation

type Selector a = a -> Bool #

A Selector is a predicate; it can simultaneously constrain the type and value of an exception.

type SpecWith a = SpecM a () #

type Spec = SpecWith () #

class ImpSpec t where Source #

Minimal complete definition

Nothing

Associated Types

type ImpSpecEnv t = (r :: Type) | r -> t Source #

type ImpSpecEnv t = Proxy t

type ImpSpecState t = (r :: Type) | r -> t Source #

type ImpSpecState t = Proxy t

Methods

impInitIO :: QCGen -> IO (ImpInit t) Source #

default impInitIO :: (ImpSpecEnv t ~ Proxy t, ImpSpecState t ~ Proxy t) => QCGen -> IO (ImpInit t) Source #

impPrepAction :: ImpM t () Source #

This will be the very first action that will run in all ImpM specs.

class StatefulGen g m => HasStatefulGen g m | m -> g where Source #

Minimal complete definition

Nothing

Methods

askStatefulGen :: m g Source #

default askStatefulGen :: MonadReader g m => m g Source #

Instances

Instances details
(HasGenEnv env g, StatefulGen g (ReaderT env m), Monad m) => HasStatefulGen g (ReaderT env m) Source # 
Instance details

Defined in Test.ImpSpec.Random

Methods

askStatefulGen :: ReaderT env m g Source #

HasStatefulGen (IOGenM QCGen) (ImpM t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

askStatefulGen :: ImpM t (IOGenM QCGen) Source #

class HasGenEnv env g | env -> g where Source #

Methods

getGenEnv :: env -> g Source #

Instances

Instances details
HasGenEnv g g Source # 
Instance details

Defined in Test.ImpSpec.Random

Methods

getGenEnv :: g -> g Source #

data ImpState t Source #

Constructors

ImpState 

data ImpEnv t Source #

Constructors

ImpEnv 

data ImpInit t Source #

Constructors

ImpInit 

Instances

Instances details
(Show (ImpSpecEnv t), Show (ImpSpecState t)) => Show (ImpInit t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

showsPrec :: Int -> ImpInit t -> ShowS #

show :: ImpInit t -> String #

showList :: [ImpInit t] -> ShowS #

(Eq (ImpSpecEnv t), Eq (ImpSpecState t)) => Eq (ImpInit t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

(==) :: ImpInit t -> ImpInit t -> Bool #

(/=) :: ImpInit t -> ImpInit t -> Bool #

(Ord (ImpSpecEnv t), Ord (ImpSpecState t)) => Ord (ImpInit t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

compare :: ImpInit t -> ImpInit t -> Ordering #

(<) :: ImpInit t -> ImpInit t -> Bool #

(<=) :: ImpInit t -> ImpInit t -> Bool #

(>) :: ImpInit t -> ImpInit t -> Bool #

(>=) :: ImpInit t -> ImpInit t -> Bool #

max :: ImpInit t -> ImpInit t -> ImpInit t #

min :: ImpInit t -> ImpInit t -> ImpInit t #

newtype ImpM t a Source #

Constructors

ImpM 

Fields

Instances

Instances details
env ~ ImpSpecEnv t => MonadReader env (ImpM t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

ask :: ImpM t env #

local :: (env -> env) -> ImpM t a -> ImpM t a #

reader :: (env -> a) -> ImpM t a #

s ~ ImpSpecState t => MonadState s (ImpM t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

get :: ImpM t s #

put :: s -> ImpM t () #

state :: (s -> (a, s)) -> ImpM t a #

MonadFail (ImpM t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

fail :: String -> ImpM t a #

MonadIO (ImpM t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

liftIO :: IO a -> ImpM t a #

Applicative (ImpM t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

pure :: a -> ImpM t a #

(<*>) :: ImpM t (a -> b) -> ImpM t a -> ImpM t b #

liftA2 :: (a -> b -> c) -> ImpM t a -> ImpM t b -> ImpM t c #

(*>) :: ImpM t a -> ImpM t b -> ImpM t b #

(<*) :: ImpM t a -> ImpM t b -> ImpM t a #

Functor (ImpM t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

fmap :: (a -> b) -> ImpM t a -> ImpM t b #

(<$) :: a -> ImpM t b -> ImpM t a #

Monad (ImpM t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

(>>=) :: ImpM t a -> (a -> ImpM t b) -> ImpM t b #

(>>) :: ImpM t a -> ImpM t b -> ImpM t b #

return :: a -> ImpM t a #

MonadGen (ImpM t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

liftGen :: Gen a -> ImpM t a #

variant :: Integral n => n -> ImpM t a -> ImpM t a #

sized :: (Int -> ImpM t a) -> ImpM t a #

resize :: Int -> ImpM t a -> ImpM t a #

choose :: Random a => (a, a) -> ImpM t a #

MonadUnliftIO (ImpM t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

withRunInIO :: ((forall a. ImpM t a -> IO a) -> IO b) -> ImpM t b #

HasStatefulGen (IOGenM QCGen) (ImpM t) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

askStatefulGen :: ImpM t (IOGenM QCGen) Source #

(ImpSpec t, Testable a) => Testable (ImpM t a) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Methods

property :: ImpM t a -> Property #

propertyForAllShrinkShow :: Gen a0 -> (a0 -> [a0]) -> (a0 -> [String]) -> (a0 -> ImpM t a) -> Property #

(ImpSpec t, Testable p) => Example (ImpM t p) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Associated Types

type Arg (ImpM t p) #

Methods

evaluateExample :: ImpM t p -> Params -> (ActionWith (Arg (ImpM t p)) -> IO ()) -> ProgressCallback -> IO Result #

(Arbitrary a, Show a, ImpSpec t, Testable p) => Example (a -> ImpM t p) Source # 
Instance details

Defined in Test.ImpSpec.Internal

Associated Types

type Arg (a -> ImpM t p) #

Methods

evaluateExample :: (a -> ImpM t p) -> Params -> (ActionWith (Arg (a -> ImpM t p)) -> IO ()) -> ProgressCallback -> IO Result #

type Arg (ImpM t p) Source # 
Instance details

Defined in Test.ImpSpec.Internal

type Arg (ImpM t p) = ImpInit t
type Arg (a -> ImpM t p) Source # 
Instance details

Defined in Test.ImpSpec.Internal

type Arg (a -> ImpM t p) = ImpInit t

data ImpException Source #

Stores extra information about the failure of the unit test

Constructors

ImpException 

Fields

assertFailure :: (HasCallStack, MonadIO m) => String -> m a Source #

Just like expectationFailure, but does not force the return type to unit. Lifted version of assertFailure

assertBool :: (HasCallStack, MonadIO m) => String -> Bool -> m () Source #

Lifted version of assertBool

arbitrary :: (Arbitrary a, MonadGen m) => m a Source #

Lifted version of arbitrary.

describe :: HasCallStack => String -> SpecWith a -> SpecWith a #

The describe function combines a list of specs into a larger spec.

xdescribe :: HasCallStack => String -> SpecWith a -> SpecWith a #

Changing describe to xdescribe marks all spec items of the corresponding subtree as pending.

This can be used to temporarily disable spec items.

it :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #

The it function creates a spec item.

A spec item consists of:

  • a textual description of a desired behavior
  • an example for that behavior
describe "absolute" $ do
  it "returns a positive number when given a negative number" $
    absolute (-1) == 1

xit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #

Changing it to xit marks the corresponding spec item as pending.

This can be used to temporarily disable a spec item.

fit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #

fit is an alias for fmap focus . it

fdescribe :: HasCallStack => String -> SpecWith a -> SpecWith a #

fdescribe is an alias for fmap focus . describe

prop :: (HasCallStack, Testable prop) => String -> prop -> Spec #

prop ".." $
  ..

is a shortcut for

it ".." $ property $
  ..

xprop :: (HasCallStack, Testable prop) => String -> prop -> Spec #

xprop ".." $
  ..

is a shortcut for

xit ".." $ property $
  ..

fprop :: (HasCallStack, Testable prop) => String -> prop -> Spec #

fprop ".." $
  ..

is a shortcut for

fit ".." $ property $
  ..

shouldBe :: (HasCallStack, MonadIO m, Show a, Eq a) => a -> a -> m () infix 1 #

actual `shouldBe` expected sets the expectation that actual is equal to expected.

shouldSatisfy :: (HasCallStack, MonadIO m, Show a) => a -> (a -> Bool) -> m () infix 1 #

v `shouldSatisfy` p sets the expectation that p v is True.

shouldStartWith :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 #

list `shouldStartWith` prefix sets the expectation that list starts with prefix,

shouldEndWith :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 #

list `shouldEndWith` suffix sets the expectation that list ends with suffix,

shouldContain :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 #

list `shouldContain` sublist sets the expectation that sublist is contained, wholly and intact, anywhere in list.

shouldMatchList :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 #

xs `shouldMatchList` ys sets the expectation that xs has the same elements that ys has, possibly in another order

shouldReturn :: (HasCallStack, MonadIO m, Show a, Eq a) => m a -> a -> m () infix 1 #

action `shouldReturn` expected sets the expectation that action returns expected.

shouldNotBe :: (HasCallStack, MonadIO m, Show a, Eq a) => a -> a -> m () infix 1 #

actual `shouldNotBe` notExpected sets the expectation that actual is not equal to notExpected

shouldNotSatisfy :: (HasCallStack, MonadIO m, Show a) => a -> (a -> Bool) -> m () infix 1 #

v `shouldNotSatisfy` p sets the expectation that p v is False.

shouldNotContain :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 #

list `shouldNotContain` sublist sets the expectation that sublist is not contained anywhere in list.

shouldNotReturn :: (HasCallStack, MonadIO m, Show a, Eq a) => m a -> a -> m () infix 1 #

action `shouldNotReturn` notExpected sets the expectation that action does not return notExpected.

shouldThrow :: (HasCallStack, Exception e, MonadUnliftIO m) => m a -> Selector e -> m () infix 1 Source #

Lifted version of shouldThrow.

uniformRM :: (HasStatefulGen g m, UniformRange a) => (a, a) -> m a Source #

uniformListM :: (HasStatefulGen g m, Uniform a) => Int -> m [a] Source #

shouldBeRight :: (HasCallStack, Show a, Show b, Eq b, MonadIO m) => Either a b -> b -> m () infix 1 Source #

Same as shouldBe, except it checks that the value is Right

shouldBeLeft :: (HasCallStack, Show a, Eq a, Show b, MonadIO m) => Either a b -> a -> m () infix 1 Source #

Same as shouldBe, except it checks that the value is Left

expectRight :: (HasCallStack, Show a, MonadIO m) => Either a b -> m b Source #

Return value on the Right and fail otherwise. Lifted version of expectRight.

expectRightDeep :: (HasCallStack, Show a, NFData b, MonadIO m) => Either a b -> m b Source #

Same as expectRight, but also evaluate the returned value to NF

expectRightDeep_ :: (HasCallStack, Show a, NFData b, MonadIO m) => Either a b -> m () Source #

Same as expectRightDeep, but discards the result

expectLeft :: (HasCallStack, Show b, MonadIO m) => Either a b -> m a Source #

Return value on the Left and fail otherwise

expectLeftDeep :: (HasCallStack, NFData a, Show b, MonadIO m) => Either a b -> m a Source #

Same as expectLeft, but also evaluate the returned value to NF

expectLeftDeep_ :: (HasCallStack, NFData a, Show b, MonadIO m) => Either a b -> m () Source #

Same as expectLeftDeep, but discards the result

shouldBeJust :: (HasCallStack, Show a, Eq a, MonadIO m) => Maybe a -> a -> m () Source #

Same as shouldBe, except it checks that the value is Just

io :: IO a -> IO a Source #

Enforce the type of expectation

Useful with polymorphic expectations that are defined below.

Example

Expand

Because shouldBeExpr is polymorphic in m, compiler will choke with a unification error. This is due to the fact that hspec's it expects a polymorphic Example.

it "MyTest" $ do
  "foo" `shouldBeExpr` "bar"

However, this is easily solved by io:

it "MyTest" $ io $ do
  "foo" `shouldBeExpr` "bar"

uniformListRM :: (HasStatefulGen g m, UniformRange a) => (a, a) -> Int -> m [a] Source #

applyQCGen :: (QCGen -> (b, QCGen)) -> ImpM t b Source #

evalImpM :: ImpSpec t => Maybe QCGen -> Maybe Int -> ImpInit t -> ImpM t b -> IO b Source #

impSetSeed :: Int -> ImpM t () Source #

Override the QuickCheck generator using a fixed seed.

evalImpGenM :: ImpSpec t => ImpInit t -> ImpM t b -> Gen (IO b) Source #

runImpGenM :: ImpSpec t => ImpInit t -> ImpM t b -> Gen (IO (b, ImpState t)) Source #

runImpM :: ImpSpec t => Maybe QCGen -> Maybe Int -> ImpInit t -> ImpM t b -> IO (b, ImpState t) Source #

execImpGenM :: ImpSpec t => ImpInit t -> ImpM t b -> Gen (IO (ImpState t)) Source #

execImpM :: ImpSpec t => Maybe QCGen -> Maybe Int -> ImpInit t -> ImpM t b -> IO (ImpState t) Source #

runImpGenM_ :: ImpSpec t => ImpInit t -> ImpM t b -> Gen (IO ()) Source #

runImpM_ :: ImpSpec t => Maybe QCGen -> Maybe Int -> ImpInit t -> ImpM t b -> IO () Source #

impAnn :: NFData a => String -> ImpM t a -> ImpM t a Source #

Annotation for when failure happens. All the logging done within annotation will be discarded if there no failures within the annotation.

impAnnDoc :: NFData a => Doc AnsiStyle -> ImpM t a -> ImpM t a Source #

logWithCallStack :: CallStack -> Doc AnsiStyle -> ImpM t () Source #

Adds a source location and Doc to the log, which are only shown if the test fails

logDoc :: HasCallStack => Doc AnsiStyle -> ImpM t () Source #

Adds a Doc to the log, which is only shown if the test fails

logText :: HasCallStack => Text -> ImpM t () Source #

Adds a Text to the log, which is only shown if the test fails

logString :: HasCallStack => String -> ImpM t () Source #

Adds a String to the log, which is only shown if the test fails