module Signet.Unstable.Type.IdTest where import qualified Data.ByteString.Char8 as Ascii import qualified Heck as Test import qualified Signet.Unstable.Exception.InvalidId as InvalidId import qualified Signet.Unstable.Type.Id as Id 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 (m :: * -> *) (n :: * -> *). Test m n -> String -> n () -> n () Test.describe Test io tree test String "Signet.Unstable.Type.Id" (tree () -> tree ()) -> tree () -> tree () forall a b. (a -> b) -> a -> b $ do Test io tree -> String -> tree () -> tree () forall (m :: * -> *) (n :: * -> *). Test m n -> String -> n () -> n () Test.describe Test io tree test String "parse" (tree () -> tree ()) -> tree () -> tree () forall a b. (a -> b) -> a -> b $ do Test io tree -> String -> io () -> tree () forall (m :: * -> *) (n :: * -> *). Test m n -> String -> m () -> n () Test.it Test io tree test String "fails with input containing separator" (io () -> tree ()) -> io () -> tree () forall a b. (a -> b) -> a -> b $ do let byteString :: ByteString byteString = String -> ByteString Ascii.pack String "invalid.id" let result :: Either InvalidId Id result = ByteString -> Either InvalidId Id Id.parse ByteString byteString Test io tree -> Either InvalidId Id -> Either InvalidId Id -> io () forall (m :: * -> *) a (n :: * -> *). (HasCallStack, Applicative m, Eq a, Show a) => Test m n -> a -> a -> m () Test.assertEq Test io tree test Either InvalidId Id result (InvalidId -> Either InvalidId Id forall a b. a -> Either a b Left (InvalidId -> Either InvalidId Id) -> InvalidId -> Either InvalidId Id forall a b. (a -> b) -> a -> b $ ByteString -> InvalidId InvalidId.MkInvalidId ByteString byteString) Test io tree -> String -> io () -> tree () forall (m :: * -> *) (n :: * -> *). Test m n -> String -> m () -> n () Test.it Test io tree test String "succeeds with valid input" (io () -> tree ()) -> io () -> tree () forall a b. (a -> b) -> a -> b $ do let byteString :: ByteString byteString = String -> ByteString Ascii.pack String "valid-id" let result :: Either InvalidId Id result = ByteString -> Either InvalidId Id Id.parse ByteString byteString Test io tree -> Either InvalidId Id -> Either InvalidId Id -> io () forall (m :: * -> *) a (n :: * -> *). (HasCallStack, Applicative m, Eq a, Show a) => Test m n -> a -> a -> m () Test.assertEq Test io tree test Either InvalidId Id result (Id -> Either InvalidId Id forall a b. b -> Either a b Right (Id -> Either InvalidId Id) -> Id -> Either InvalidId Id forall a b. (a -> b) -> a -> b $ ByteString -> Id Id.MkId ByteString byteString) Test io tree -> String -> tree () -> tree () forall (m :: * -> *) (n :: * -> *). Test m n -> String -> n () -> n () Test.describe Test io tree test String "render" (tree () -> tree ()) -> tree () -> tree () forall a b. (a -> b) -> a -> b $ do Test io tree -> String -> io () -> tree () forall (m :: * -> *) (n :: * -> *). Test m n -> String -> m () -> n () Test.it Test io tree test String "returns the original ByteString" (io () -> tree ()) -> io () -> tree () forall a b. (a -> b) -> a -> b $ do let byteString :: ByteString byteString = String -> ByteString Ascii.pack String "valid-id" let id_ :: Id id_ = ByteString -> Id Id.MkId ByteString byteString Test io tree -> ByteString -> ByteString -> io () forall (m :: * -> *) a (n :: * -> *). (HasCallStack, Applicative m, Eq a, Show a) => Test m n -> a -> a -> m () Test.assertEq Test io tree test (Id -> ByteString Id.render Id id_) ByteString byteString