module Signet.Unstable.Type.PublicKeyTest where import qualified Control.Monad.Catch as Exception import qualified Crypto.Error as Error import qualified Crypto.PubKey.Ed25519 as Ed25519 import qualified Data.ByteString.Char8 as Ascii import qualified Signet.Unstable.Exception.InvalidPublicKey as InvalidPublicKey import qualified Signet.Unstable.Extra.Either as Either import qualified Signet.Unstable.Type.PublicKey as PublicKey import qualified Signet.Unstable.Type.Test as Test spec :: (Exception.MonadThrow io, Monad tree) => Test.Test io tree -> tree () spec :: forall (io :: * -> *) (tree :: * -> *). (MonadThrow 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.Type.PublicKey" (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 "parse" (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 "fails with invalid prefix" (io () -> tree ()) -> io () -> tree () forall a b. (a -> b) -> a -> b $ do let byteString :: ByteString byteString = String -> ByteString Ascii.pack String "invalid" let result :: Either InvalidPublicKey PublicKey result = ByteString -> Either InvalidPublicKey PublicKey PublicKey.parse ByteString byteString Test io tree -> Either InvalidPublicKey PublicKey -> Either InvalidPublicKey PublicKey -> 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 InvalidPublicKey PublicKey result (InvalidPublicKey -> Either InvalidPublicKey PublicKey forall a b. a -> Either a b Left (ByteString -> InvalidPublicKey InvalidPublicKey.MkInvalidPublicKey ByteString byteString)) Test io tree -> String -> io () -> tree () forall (io :: * -> *) (tree :: * -> *). Test io tree -> String -> io () -> tree () Test.it Test io tree test String "fails with invalid input" (io () -> tree ()) -> io () -> tree () forall a b. (a -> b) -> a -> b $ do let byteString :: ByteString byteString = String -> ByteString Ascii.pack String "whpk_invalid" let result :: Either InvalidPublicKey PublicKey result = ByteString -> Either InvalidPublicKey PublicKey PublicKey.parse ByteString byteString Test io tree -> Either InvalidPublicKey PublicKey -> Either InvalidPublicKey PublicKey -> 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 InvalidPublicKey PublicKey result (InvalidPublicKey -> Either InvalidPublicKey PublicKey forall a b. a -> Either a b Left (ByteString -> InvalidPublicKey InvalidPublicKey.MkInvalidPublicKey ByteString byteString)) Test io tree -> String -> io () -> tree () forall (io :: * -> *) (tree :: * -> *). Test io tree -> String -> io () -> tree () Test.it Test io tree test String "succeeds with valid input" (io () -> tree ()) -> io () -> tree () forall a b. (a -> b) -> a -> b $ do let result :: Either InvalidPublicKey PublicKey result = ByteString -> Either InvalidPublicKey PublicKey PublicKey.parse (ByteString -> Either InvalidPublicKey PublicKey) -> ByteString -> Either InvalidPublicKey PublicKey forall a b. (a -> b) -> a -> b $ String -> ByteString Ascii.pack String "whpk_QUJDREVGR0hJSktMTU5PUFFSU1RVVldYWVowMTIzNDU=" publicKey <- Either CryptoError PublicKey -> io PublicKey forall e (m :: * -> *) a. (Exception e, MonadThrow m) => Either e a -> m a Either.throw (Either CryptoError PublicKey -> io PublicKey) -> (ByteString -> Either CryptoError PublicKey) -> ByteString -> io PublicKey forall b c a. (b -> c) -> (a -> b) -> a -> c . (PublicKey -> PublicKey) -> Either CryptoError PublicKey -> Either CryptoError PublicKey forall a b. (a -> b) -> Either CryptoError a -> Either CryptoError b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap PublicKey -> PublicKey PublicKey.MkPublicKey (Either CryptoError PublicKey -> Either CryptoError PublicKey) -> (ByteString -> Either CryptoError PublicKey) -> ByteString -> Either CryptoError PublicKey forall b c a. (b -> c) -> (a -> b) -> a -> c . CryptoFailable PublicKey -> Either CryptoError PublicKey forall a. CryptoFailable a -> Either CryptoError a Error.eitherCryptoError (CryptoFailable PublicKey -> Either CryptoError PublicKey) -> (ByteString -> CryptoFailable PublicKey) -> ByteString -> Either CryptoError PublicKey forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> CryptoFailable PublicKey forall ba. ByteArrayAccess ba => ba -> CryptoFailable PublicKey Ed25519.publicKey (ByteString -> io PublicKey) -> ByteString -> io PublicKey forall a b. (a -> b) -> a -> b $ String -> ByteString Ascii.pack String "ABCDEFGHIJKLMNOPQRSTUVWXYZ012345" Test.assertEq test result (Right publicKey) Test io tree -> String -> tree () -> tree () forall (io :: * -> *) (tree :: * -> *). Test io tree -> String -> tree () -> tree () 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 (io :: * -> *) (tree :: * -> *). Test io tree -> String -> io () -> tree () Test.it Test io tree test String "works" (io () -> tree ()) -> io () -> tree () forall a b. (a -> b) -> a -> b $ do publicKey <- Either CryptoError PublicKey -> io PublicKey forall e (m :: * -> *) a. (Exception e, MonadThrow m) => Either e a -> m a Either.throw (Either CryptoError PublicKey -> io PublicKey) -> (ByteString -> Either CryptoError PublicKey) -> ByteString -> io PublicKey forall b c a. (b -> c) -> (a -> b) -> a -> c . (PublicKey -> PublicKey) -> Either CryptoError PublicKey -> Either CryptoError PublicKey forall a b. (a -> b) -> Either CryptoError a -> Either CryptoError b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap PublicKey -> PublicKey PublicKey.MkPublicKey (Either CryptoError PublicKey -> Either CryptoError PublicKey) -> (ByteString -> Either CryptoError PublicKey) -> ByteString -> Either CryptoError PublicKey forall b c a. (b -> c) -> (a -> b) -> a -> c . CryptoFailable PublicKey -> Either CryptoError PublicKey forall a. CryptoFailable a -> Either CryptoError a Error.eitherCryptoError (CryptoFailable PublicKey -> Either CryptoError PublicKey) -> (ByteString -> CryptoFailable PublicKey) -> ByteString -> Either CryptoError PublicKey forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> CryptoFailable PublicKey forall ba. ByteArrayAccess ba => ba -> CryptoFailable PublicKey Ed25519.publicKey (ByteString -> io PublicKey) -> ByteString -> io PublicKey forall a b. (a -> b) -> a -> b $ String -> ByteString Ascii.pack String "ABCDEFGHIJKLMNOPQRSTUVWXYZ012345" Test.assertEq test (PublicKey.render publicKey) (Ascii.pack "whpk_QUJDREVGR0hJSktMTU5PUFFSU1RVVldYWVowMTIzNDU=")