HMock-0.1.0.0: A flexible mock framework for testing effectful code.
Safe HaskellNone
LanguageHaskell2010

Test.HMock.Internal.Expectable

Synopsis

Documentation

class Expectable cls name m r e | e -> cls name m r where Source #

Something that can be expected. This type class covers a number of cases:

  • Expecting an exact Action.
  • Expecting anything that matches a Matcher.
  • Adding a return value (with |->) or response (with |=>).

Methods

toRule :: e -> Rule cls name m r Source #

Instances

Instances details
Expectable cls name m r (Matcher cls name m r) Source # 
Instance details

Defined in Test.HMock.Internal.Expectable

Methods

toRule :: Matcher cls name m r -> Rule cls name m r Source #

Expectable cls name m r (Rule cls name m r) Source # 
Instance details

Defined in Test.HMock.Internal.Expectable

Methods

toRule :: Rule cls name m r -> Rule cls name m r Source #

data Rule (cls :: (Type -> Type) -> Constraint) (name :: Symbol) (m :: Type -> Type) (r :: Type) where Source #

A rule for matching a method and responding to it when it matches.

The method may be matched by providing either an Action to match exactly, or a Matcher. Exact matching is only available when all method arguments

A Rule may have zero or more responses, which are attached using |-> and |=>. If there are no responses for a Rule, then there must be a default response for that action, and it is used. If more than one response is added, the rule will perform the responses in order, repeating the last response if there are additional matches.

Example:

expect $
  GetLine_ anything
    |-> "hello"
    |=> (GetLine prompt) -> "The prompt was " ++ prompt
    |-> "quit"

Constructors

(:=>) :: Matcher cls name m r -> [Action cls name m r -> MockT m r] -> Rule cls name m r 

Instances

Instances details
Expectable cls name m r (Rule cls name m r) Source # 
Instance details

Defined in Test.HMock.Internal.Expectable

Methods

toRule :: Rule cls name m r -> Rule cls name m r Source #

(|=>) :: Expectable cls name m r expectable => expectable -> (Action cls name m r -> MockT m r) -> Rule cls name m r infixl 1 Source #

Attaches a response to an expectation. This is a very flexible response, which can look at arguments, do things in the base monad, set up more expectations, etc. The matching Action is passed to the response, and is guaranteed to be a match so it's fine to just pattern match on the correct method.

(|->) :: (Monad m, Expectable cls name m r expectable) => expectable -> r -> Rule cls name m r infixl 1 Source #

Attaches a return value to an expectation. This is more convenient than |=> in the common case where you just want to return a known result. e |-> r means the same thing as e |=> const (return r).

type MockableMethod (cls :: (Type -> Type) -> Constraint) (name :: Symbol) (m :: Type -> Type) (r :: Type) = (Mockable cls, Typeable m, KnownSymbol name, Typeable r) Source #

All constraints needed to mock a method with the given class, name, base monad, and return type.

data SingleRule (cls :: (Type -> Type) -> Constraint) (name :: Symbol) (m :: Type -> Type) (r :: Type) where Source #

A Rule that contains only a single response. This is the target for desugaring the multi-response rule format.

Constructors

(:->) :: Matcher cls name m r -> Maybe (Action cls name m r -> MockT m r) -> SingleRule cls name m r 

data Step m where Source #

A single step of an expectation.

Constructors

Step :: MockableMethod cls name m r => Located (SingleRule cls name m r) -> Step m 

Instances

Instances details
Show (Step m) Source # 
Instance details

Defined in Test.HMock.Internal.Expectable

Methods

showsPrec :: Int -> Step m -> ShowS #

show :: Step m -> String #

showList :: [Step m] -> ShowS #

expandRule :: MockableMethod cls name m r => CallStack -> Rule cls name m r -> ExpectSet (Step m) Source #

Expands a Rule into an expectation. The expected multiplicity will be one if there are no responses; otherwise one call is expected per response.

expandRepeatRule :: MockableMethod cls name m r => Multiplicity -> CallStack -> Rule cls name m r -> ExpectSet (Step m) Source #

Expands a Rule into an expectation, given a target multiplicity. It is an error if there are too many responses for the multiplicity. If there are too few responses, the last response will be repeated.

class ExpectContext (t :: (Type -> Type) -> Type -> Type) where Source #

Type class for contexts in which it makes sense to express an expectation. Notably, this includes MockT, which expects actions to be performed during a test.

Methods

fromExpectSet :: MonadIO m => ExpectSet (Step m) -> t m () Source #

Instances

Instances details
ExpectContext MockT Source # 
Instance details

Defined in Test.HMock.Internal.MockT

Methods

fromExpectSet :: forall (m :: Type -> Type). MonadIO m => ExpectSet (Step m) -> MockT m () Source #

ExpectContext Expected Source # 
Instance details

Defined in Test.HMock.Internal.Expectable

Methods

fromExpectSet :: forall (m :: Type -> Type). MonadIO m => ExpectSet (Step m) -> Expected m () Source #

newtype Expected m a Source #

Constructors

Expected 

Instances

Instances details
ExpectContext Expected Source # 
Instance details

Defined in Test.HMock.Internal.Expectable

Methods

fromExpectSet :: forall (m :: Type -> Type). MonadIO m => ExpectSet (Step m) -> Expected m () Source #

expect :: (HasCallStack, MonadIO m, MockableMethod cls name m r, Expectable cls name m r expectable, ExpectContext ctx) => expectable -> ctx m () Source #

Creates an expectation that an action is performed once per given response (or exactly once if there is no response).

runMockT $ do
  expect $
    ReadFile "foo.txt"
      |-> "lorem ipsum"
      |-> "oops, the file changed out from under me!"
  callCodeUnderTest

In this example, readFile must be called exactly twice by the tested code, and will return "lorem ipsum" the first time, but something different the second time.

expectN Source #

Arguments

:: (HasCallStack, MonadIO m, MockableMethod cls name m r, Expectable cls name m r expectable, ExpectContext ctx) 
=> Multiplicity

The number of times the action should be performed.

-> expectable

The action and its response.

-> ctx m () 

Creates an expectation that an action is performed some number of times.

  runMockT $ do
    expect $ MakeList
    expectN (atLeast 2) $
      CheckList "Cindy Lou Who" |-> "nice"

    callCodeUnderTest

expectAny :: (HasCallStack, MonadIO m, MockableMethod cls name m r, Expectable cls name m r expectable, ExpectContext ctx) => expectable -> ctx m () Source #

Specifies a response if a matching action is performed, but doesn't expect anything. This is equivalent to expectN anyMultiplicity, but shorter.

In this example, the later use of whenever overrides earlier uses, but only for calls that match its conditions.

  runMockT $ do
    whenever $ ReadFile_ anything |-> "tlhIngan maH!"
    whenever $ ReadFile "config.txt" |-> "lang: klingon"

    callCodeUnderTest

inSequence :: (MonadIO m, ExpectContext ctx) => (forall ctx'. ExpectContext ctx' => [ctx' m ()]) -> ctx m () Source #

Creates a sequential expectation. Other actions can still happen during the sequence, but these specific expectations must be met in this order.

  inSequence
    [ expect $ MoveForward,
      expect $ TurnRight,
      expect $ MoveForward
    ]

Beware of using inSequence too often. It is appropriate when the property you are testing is that the order of effects is correct. If that's not the purpose of the test, consider adding several independent expectations, instead. This avoids over-asserting, and keeps your tests less brittle.

inAnyOrder :: (MonadIO m, ExpectContext ctx) => (forall ctx'. ExpectContext ctx' => [ctx' m ()]) -> ctx m () Source #

Combines multiple expectations, which can occur in any order. Most of the time, you can achieve the same thing by expecting each separately, but this can be combined in complex expectations to describe more complex ordering constraints.

  inSequence
    [ inAnyOrder
        [ expect $ AdjustMirrors,
          expect $ FastenSeatBelt
        ],
      expect $ StartCar
    ]

anyOf :: (MonadIO m, ExpectContext ctx) => (forall ctx'. ExpectContext ctx' => [ctx' m ()]) -> ctx m () Source #

Combines multiple expectations, requiring exactly one of them to occur.

  anyOf
    [ expect $ ApplyForJob,
      expect $ ApplyForUniversity
    ]

times :: (MonadIO m, ExpectContext ctx) => Multiplicity -> (forall ctx'. ExpectContext ctx' => ctx' m ()) -> ctx m () Source #

Creates a parent expectation that the child expectation will happen a certain number of times. Unlike expectN, the child expectation can be arbitrarily complex and span multiple actions. Also unlike expectN, each new execution will restart response sequences for rules with more than one response.

Different occurrences of the child can be interleaved. In case of ambiguity, progressing on an existing occurrence is preferred over starting a new occurrence.

consecutiveTimes :: (MonadIO m, ExpectContext ctx) => Multiplicity -> (forall ctx'. ExpectContext ctx' => ctx' m ()) -> ctx m () Source #

Creates a parent expectation that the child expectation will happen a certain number of times. Unlike expectN, the child expectation can be arbitrarily complex and span multiple actions. Also unlike expectN, each new execution will restart response sequences for rules with more than one response.

Different occurrences of the child must happen consecutively, with one finishing before the next begins.