Skip to content

Commit

Permalink
adding shouldReturnException function
Browse files Browse the repository at this point in the history
  • Loading branch information
akhesacaro-fretlink committed Mar 15, 2021
1 parent 135309d commit 356f852
Show file tree
Hide file tree
Showing 2 changed files with 26 additions and 0 deletions.
2 changes: 2 additions & 0 deletions hspec-expectations-lifted.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,10 @@ library
-Wall
build-depends:
base == 4.*
, exceptions
, hspec-expectations >= 0.8.2
, transformers
, mtl
hs-source-dirs:
src
exposed-modules:
Expand Down
24 changes: 24 additions & 0 deletions src/Test/Hspec/Expectations/Lifted.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
-- |
-- Introductory documentation: <https://github.com/hspec/hspec-expectations#readme>
module Test.Hspec.Expectations.Lifted (
Expand All @@ -14,6 +15,8 @@ module Test.Hspec.Expectations.Lifted (
, shouldMatchList
, shouldReturn

, shouldThrowException

, shouldNotBe
, shouldNotSatisfy
, shouldNotContain
Expand All @@ -23,7 +26,11 @@ module Test.Hspec.Expectations.Lifted (
, HasCallStack
) where

import Control.Monad (unless)
import Control.Monad.IO.Class
import Control.Monad.Catch (MonadCatch, try)
import Control.Exception (Exception)
import Data.Typeable (typeOf)
import qualified Test.Hspec.Expectations as E
import Test.Hspec.Expectations (HasCallStack)

Expand Down Expand Up @@ -97,3 +104,20 @@ shouldNotContain = liftIO2 E.shouldNotContain
-- does not return @notExpected@.
shouldNotReturn :: (HasCallStack, MonadIO m, Show a, Eq a) => m a -> a -> m ()
shouldNotReturn action expected = action >>= liftIO . (`E.shouldNotBe` expected)

-- |
-- @action \`shouldThrowException\` expected@ Exception
shouldThrowException :: forall m a e. (HasCallStack, MonadIO m, MonadCatch m, Exception e, Eq e) => m a -> e -> m ()
action `shouldThrowException` e = do
r <- try action
case r of
Right _ ->
expectationFailure $
"did not get expected exception: " <> exceptionType e
Left err -> unless (err == e) $
expectationFailure $
"predicate failed on expected exception: "
<> exceptionType e
<> " (" <> show err <> ")"
where
exceptionType = (show . typeOf)

0 comments on commit 356f852

Please sign in to comment.