module Signet.Unstable.Extra.EitherTest where import qualified Control.Monad.Catch as Exception import qualified Data.Void as Void import qualified Signet.Unstable.Extra.Either as Either import qualified Signet.Unstable.Type.Test as Test spec :: (Exception.MonadCatch io, Monad tree) => Test.Test io tree -> tree () spec :: forall (io :: * -> *) (tree :: * -> *). (MonadCatch io, Monad tree) => Test io tree -> tree () spec Test io tree test = Test io tree -> String -> tree () -> tree () forall (io :: * -> *) (tree :: * -> *). Test io tree -> String -> tree () -> tree () Test.describe Test io tree test String "Signet.Unstable.Extra.Either" (tree () -> tree ()) -> tree () -> tree () forall a b. (a -> b) -> a -> b $ do Test io tree -> String -> tree () -> tree () forall (io :: * -> *) (tree :: * -> *). Test io tree -> String -> tree () -> tree () Test.describe Test io tree test String "hush" (tree () -> tree ()) -> tree () -> tree () forall a b. (a -> b) -> a -> b $ do Test io tree -> String -> io () -> tree () forall (io :: * -> *) (tree :: * -> *). Test io tree -> String -> io () -> tree () Test.it Test io tree test String "works with Left" (io () -> tree ()) -> io () -> tree () forall a b. (a -> b) -> a -> b $ do Test io tree -> Maybe Void -> Maybe Void -> io () forall (io :: * -> *) a (tree :: * -> *). (HasCallStack, Applicative io, Eq a, Show a) => Test io tree -> a -> a -> io () Test.assertEq Test io tree test (Either () Void -> Maybe Void forall x a. Either x a -> Maybe a Either.hush (() -> Either () Void forall a b. a -> Either a b Left () :: Either () Void.Void)) Maybe Void forall a. Maybe a Nothing Test io tree -> String -> io () -> tree () forall (io :: * -> *) (tree :: * -> *). Test io tree -> String -> io () -> tree () Test.it Test io tree test String "works with Right" (io () -> tree ()) -> io () -> tree () forall a b. (a -> b) -> a -> b $ do Test io tree -> Maybe () -> Maybe () -> io () forall (io :: * -> *) a (tree :: * -> *). (HasCallStack, Applicative io, Eq a, Show a) => Test io tree -> a -> a -> io () Test.assertEq Test io tree test (Either Void () -> Maybe () forall x a. Either x a -> Maybe a Either.hush (() -> Either Void () forall a b. b -> Either a b Right () :: Either Void.Void ())) (() -> Maybe () forall a. a -> Maybe a Just ()) Test io tree -> String -> tree () -> tree () forall (io :: * -> *) (tree :: * -> *). Test io tree -> String -> tree () -> tree () Test.describe Test io tree test String "throw" (tree () -> tree ()) -> tree () -> tree () forall a b. (a -> b) -> a -> b $ do Test io tree -> String -> io () -> tree () forall (io :: * -> *) (tree :: * -> *). Test io tree -> String -> io () -> tree () Test.it Test io tree test String "throws an exception for Left" (io () -> tree ()) -> io () -> tree () forall a b. (a -> b) -> a -> b $ do result <- io Void -> io (Either TestException Void) forall (m :: * -> *) e a. (HasCallStack, MonadCatch m, Exception e) => m a -> m (Either e a) Exception.try (io Void -> io (Either TestException Void)) -> (Either TestException Void -> io Void) -> Either TestException Void -> io (Either TestException Void) forall b c a. (b -> c) -> (a -> b) -> a -> c . Either TestException Void -> io Void forall e (m :: * -> *) a. (Exception e, MonadThrow m) => Either e a -> m a Either.throw (Either TestException Void -> io (Either TestException Void)) -> Either TestException Void -> io (Either TestException Void) forall a b. (a -> b) -> a -> b $ TestException -> Either TestException Void forall a b. a -> Either a b Left TestException MkTestException Test.assertEq test result (Left MkTestException :: Either TestException Void.Void) Test io tree -> String -> io () -> tree () forall (io :: * -> *) (tree :: * -> *). Test io tree -> String -> io () -> tree () Test.it Test io tree test String "returns the value for Right" (io () -> tree ()) -> io () -> tree () forall a b. (a -> b) -> a -> b $ do value <- Either Void () -> io () forall e (m :: * -> *) a. (Exception e, MonadThrow m) => Either e a -> m a Either.throw (() -> Either Void () forall a b. b -> Either a b Right () :: Either Void.Void ()) Test.assertEq test value () data TestException = MkTestException deriving (TestException -> TestException -> Bool (TestException -> TestException -> Bool) -> (TestException -> TestException -> Bool) -> Eq TestException forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: TestException -> TestException -> Bool == :: TestException -> TestException -> Bool $c/= :: TestException -> TestException -> Bool /= :: TestException -> TestException -> Bool Eq, Int -> TestException -> ShowS [TestException] -> ShowS TestException -> String (Int -> TestException -> ShowS) -> (TestException -> String) -> ([TestException] -> ShowS) -> Show TestException forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> TestException -> ShowS showsPrec :: Int -> TestException -> ShowS $cshow :: TestException -> String show :: TestException -> String $cshowList :: [TestException] -> ShowS showList :: [TestException] -> ShowS Show) instance Exception.Exception TestException