module Test.Hspec.Benri (
endsThen,
endsJust,
endsJust_,
endsNothing,
endsLeft,
endsLeft_,
endsRight,
endsRight_,
) where
import Data.Maybe (isJust)
import Test.Hspec (Expectation, HasCallStack, shouldBe, shouldSatisfy)
endsRight :: (HasCallStack, Show a, Eq a, Show b, Eq b) => IO (Either a b) -> b -> Expectation
IO (Either a b)
action endsRight :: forall a b.
(HasCallStack, Show a, Eq a, Show b, Eq b) =>
IO (Either a b) -> b -> Expectation
`endsRight` b
expected = IO (Either a b)
action forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` forall a b. b -> Either a b
Right b
expected)
endsLeft ::
(HasCallStack, Show a, Eq a, Show b, Eq b) => IO (Either a b) -> a -> Expectation
IO (Either a b)
action endsLeft :: forall a b.
(HasCallStack, Show a, Eq a, Show b, Eq b) =>
IO (Either a b) -> a -> Expectation
`endsLeft` a
expected = IO (Either a b)
action forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` forall a b. a -> Either a b
Left a
expected)
endsRight_ :: (Show a, Show b) => IO (Either a b) -> IO ()
endsRight_ :: forall a b. (Show a, Show b) => IO (Either a b) -> Expectation
endsRight_ IO (Either a b)
action = forall a. Show a => IO a -> (a -> Bool) -> Expectation
endsThen IO (Either a b)
action forall a b. (a -> b) -> a -> b
$ forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const Bool
False) (forall a b. a -> b -> a
const Bool
True)
endsLeft_ :: (Show a, Show b) => IO (Either a b) -> IO ()
endsLeft_ :: forall a b. (Show a, Show b) => IO (Either a b) -> Expectation
endsLeft_ IO (Either a b)
action = forall a. Show a => IO a -> (a -> Bool) -> Expectation
endsThen IO (Either a b)
action forall a b. (a -> b) -> a -> b
$ forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const Bool
True) (forall a b. a -> b -> a
const Bool
False)
endsJust ::
(HasCallStack, Show a, Eq a) => IO (Maybe a) -> a -> Expectation
IO (Maybe a)
action endsJust :: forall a.
(HasCallStack, Show a, Eq a) =>
IO (Maybe a) -> a -> Expectation
`endsJust` a
expected = IO (Maybe a)
action forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` forall a. a -> Maybe a
Just a
expected)
endsNothing :: (Show a, Eq a) => IO (Maybe a) -> IO ()
endsNothing :: forall a. (Show a, Eq a) => IO (Maybe a) -> Expectation
endsNothing IO (Maybe a)
action = IO (Maybe a)
action forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` forall a. Maybe a
Nothing)
endsJust_ :: (Show a) => IO (Maybe a) -> IO ()
endsJust_ :: forall a. Show a => IO (Maybe a) -> Expectation
endsJust_ IO (Maybe a)
action = forall a. Show a => IO a -> (a -> Bool) -> Expectation
endsThen IO (Maybe a)
action forall a. Maybe a -> Bool
isJust
endsThen :: (Show a) => IO a -> (a -> Bool) -> IO ()
endsThen :: forall a. Show a => IO a -> (a -> Bool) -> Expectation
endsThen IO a
action a -> Bool
p = IO a
action forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (forall a. (HasCallStack, Show a) => a -> (a -> Bool) -> Expectation
`shouldSatisfy` a -> Bool
p)
infix 1 `endsLeft`, `endsRight`, `endsThen`, `endsJust`