{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -Wno-incomplete-patterns #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Test.Fluent.Assertions.Either (isLeft, isRight, extractingRight, extractingLeft) where
import qualified Data.Either as Either
import GHC.Stack (HasCallStack)
import Test.Fluent.Assertions
( Assertion,
Assertion',
focus,
forceError,
inside,
simpleAssertion,
)
isLeft :: HasCallStack => Assertion (Either a b)
isLeft :: Assertion (Either a b)
isLeft = (Either a b -> Bool) -> Assertion Bool -> Assertion (Either a b)
forall b a. (b -> a) -> Assertion a -> Assertion b
inside Either a b -> Bool
forall a b. Either a b -> Bool
Either.isLeft ((Bool -> Bool) -> (Bool -> String) -> Assertion Bool
forall a.
HasCallStack =>
(a -> Bool) -> (a -> String) -> Assertion a
simpleAssertion (Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool
True) Bool -> String
forall p p. IsString p => p -> p
assertionMessage)
where
assertionMessage :: p -> p
assertionMessage p
_ = p
"should be Left, but is Right"
isRight :: HasCallStack => Assertion (Either a b)
isRight :: Assertion (Either a b)
isRight = (Either a b -> Bool) -> Assertion Bool -> Assertion (Either a b)
forall b a. (b -> a) -> Assertion a -> Assertion b
inside Either a b -> Bool
forall a b. Either a b -> Bool
Either.isRight ((Bool -> Bool) -> (Bool -> String) -> Assertion Bool
forall a.
HasCallStack =>
(a -> Bool) -> (a -> String) -> Assertion a
simpleAssertion (Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool
True) Bool -> String
forall p p. IsString p => p -> p
assertionMessage)
where
assertionMessage :: p -> p
assertionMessage p
_ = p
"should be Right, but is Left"
extractingRight :: HasCallStack => Assertion' (Either a b) b
= Assertion (Either a b) -> Assertion (Either a b)
forall a. Assertion a -> Assertion a
forceError Assertion (Either a b)
forall a b. HasCallStack => Assertion (Either a b)
isRight Assertion (Either a b)
-> Assertion' (Either a b) b -> Assertion' (Either a b) b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either a b -> b) -> Assertion' (Either a b) b
forall a b. (a -> b) -> Assertion' a b
focus (\case (Right b
a) -> b
a)
extractingLeft :: HasCallStack => Assertion' (Either a b) a
= Assertion (Either a b) -> Assertion (Either a b)
forall a. Assertion a -> Assertion a
forceError Assertion (Either a b)
forall a b. HasCallStack => Assertion (Either a b)
isLeft Assertion (Either a b)
-> Assertion' (Either a b) a -> Assertion' (Either a b) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either a b -> a) -> Assertion' (Either a b) a
forall a b. (a -> b) -> Assertion' a b
focus (\case (Left a
a) -> a
a)