{-# LANGUAGE CPP #-}
module Test.Hspec.Expectations.Contrib (
isLeft
, isRight
, annotate
) where
import Control.Exception
import Test.HUnit.Lang (HUnitFailure(..), FailureReason(..))
#if MIN_VERSION_base(4,7,0)
import Data.Either
#else
isLeft :: Either a b -> Bool
{-# DEPRECATED isLeft "use Data.Either.Compat.isLeft from package base-compat instead" #-}
isLeft (Left _) = True
isLeft (Right _) = False
isRight :: Either a b -> Bool
{-# DEPRECATED isRight "use Data.Either.Compat.isRight from package base-compat instead" #-}
isRight (Left _) = False
isRight (Right _) = True
#endif
annotate :: String -> IO a -> IO a
annotate :: forall a. String -> IO a -> IO a
annotate String
message = (HUnitFailure -> IO a) -> IO a -> IO a
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle ((HUnitFailure -> IO a) -> IO a -> IO a)
-> (HUnitFailure -> IO a) -> IO a -> IO a
forall a b. (a -> b) -> a -> b
$ \ (HUnitFailure Maybe SrcLoc
loc FailureReason
reason) -> HUnitFailure -> IO a
forall e a. Exception e => e -> IO a
throwIO (HUnitFailure -> IO a)
-> (FailureReason -> HUnitFailure) -> FailureReason -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe SrcLoc -> FailureReason -> HUnitFailure
HUnitFailure Maybe SrcLoc
loc (FailureReason -> IO a) -> FailureReason -> IO a
forall a b. (a -> b) -> a -> b
$ case FailureReason
reason of
Reason String
err -> String -> FailureReason
Reason (String -> FailureReason) -> String -> FailureReason
forall a b. (a -> b) -> a -> b
$ String -> String
addMessage String
err
ExpectedButGot Maybe String
err String
expected String
got -> Maybe String -> String -> String -> FailureReason
ExpectedButGot (String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ String -> (String -> String) -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
message String -> String
addMessage Maybe String
err) String
expected String
got
where
addMessage :: String -> String
addMessage String
err
| String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
err = String
message
| Bool
otherwise = String
message String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
err