module Signet.Unstable.Extra.MaybeTest where import qualified Data.Void as Void import qualified Signet.Unstable.Extra.Maybe as Maybe import qualified Signet.Unstable.Type.Test as Test spec :: (Applicative io, Monad tree) => Test.Test io tree -> tree () spec :: forall (io :: * -> *) (tree :: * -> *). (Applicative 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.Maybe" (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 "note" (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 nothing" (io () -> tree ()) -> io () -> tree () forall a b. (a -> b) -> a -> b $ do Test io tree -> Either () Void -> Either () 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 (() -> Maybe Void -> Either () Void forall e a. e -> Maybe a -> Either e a Maybe.note () (Maybe Void forall a. Maybe a Nothing :: Maybe Void.Void)) (() -> Either () Void forall a b. a -> Either a b Left ()) Test io tree -> String -> io () -> tree () forall (io :: * -> *) (tree :: * -> *). Test io tree -> String -> io () -> tree () Test.it Test io tree test String "works with just" (io () -> tree ()) -> io () -> tree () forall a b. (a -> b) -> a -> b $ do Test io tree -> Either () Bool -> Either () Bool -> io () forall (io :: * -> *) a (tree :: * -> *). (HasCallStack, Applicative io, Eq a, Show a) => Test io tree -> a -> a -> io () Test.assertEq Test io tree test (() -> Maybe Bool -> Either () Bool forall e a. e -> Maybe a -> Either e a Maybe.note () (Bool -> Maybe Bool forall a. a -> Maybe a Just Bool True)) (Bool -> Either () Bool forall a b. b -> Either a b Right Bool True)