module Signet.Unstable.Type.SecretKeyTest 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.InvalidSecretKey as InvalidSecretKey import qualified Signet.Unstable.Extra.Either as Either import qualified Signet.Unstable.Type.SecretKey as SecretKey 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.SecretKey" (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 InvalidSecretKey SecretKey result = ByteString -> Either InvalidSecretKey SecretKey SecretKey.parse ByteString byteString Test io tree -> Either InvalidSecretKey SecretKey -> Either InvalidSecretKey SecretKey -> 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 InvalidSecretKey SecretKey result (InvalidSecretKey -> Either InvalidSecretKey SecretKey forall a b. a -> Either a b Left (ByteString -> InvalidSecretKey InvalidSecretKey.MkInvalidSecretKey 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 "whsk_invalid" let result :: Either InvalidSecretKey SecretKey result = ByteString -> Either InvalidSecretKey SecretKey SecretKey.parse ByteString byteString Test io tree -> Either InvalidSecretKey SecretKey -> Either InvalidSecretKey SecretKey -> 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 InvalidSecretKey SecretKey result (InvalidSecretKey -> Either InvalidSecretKey SecretKey forall a b. a -> Either a b Left (ByteString -> InvalidSecretKey InvalidSecretKey.MkInvalidSecretKey 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 InvalidSecretKey SecretKey result = ByteString -> Either InvalidSecretKey SecretKey SecretKey.parse (ByteString -> Either InvalidSecretKey SecretKey) -> ByteString -> Either InvalidSecretKey SecretKey forall a b. (a -> b) -> a -> b $ String -> ByteString Ascii.pack String "whsk_QUJDREVGR0hJSktMTU5PUFFSU1RVVldYWVowMTIzNDU=" secretKey <- Either CryptoError SecretKey -> io SecretKey forall e (m :: * -> *) a. (Exception e, MonadThrow m) => Either e a -> m a Either.throw (Either CryptoError SecretKey -> io SecretKey) -> (ByteString -> Either CryptoError SecretKey) -> ByteString -> io SecretKey forall b c a. (b -> c) -> (a -> b) -> a -> c . (SecretKey -> SecretKey) -> Either CryptoError SecretKey -> Either CryptoError SecretKey forall a b. (a -> b) -> Either CryptoError a -> Either CryptoError b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap SecretKey -> SecretKey SecretKey.MkSecretKey (Either CryptoError SecretKey -> Either CryptoError SecretKey) -> (ByteString -> Either CryptoError SecretKey) -> ByteString -> Either CryptoError SecretKey forall b c a. (b -> c) -> (a -> b) -> a -> c . CryptoFailable SecretKey -> Either CryptoError SecretKey forall a. CryptoFailable a -> Either CryptoError a Error.eitherCryptoError (CryptoFailable SecretKey -> Either CryptoError SecretKey) -> (ByteString -> CryptoFailable SecretKey) -> ByteString -> Either CryptoError SecretKey forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> CryptoFailable SecretKey forall ba. ByteArrayAccess ba => ba -> CryptoFailable SecretKey Ed25519.secretKey (ByteString -> io SecretKey) -> ByteString -> io SecretKey forall a b. (a -> b) -> a -> b $ String -> ByteString Ascii.pack String "ABCDEFGHIJKLMNOPQRSTUVWXYZ012345" Test.assertEq test result (Right secretKey) 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 secretKey <- Either CryptoError SecretKey -> io SecretKey forall e (m :: * -> *) a. (Exception e, MonadThrow m) => Either e a -> m a Either.throw (Either CryptoError SecretKey -> io SecretKey) -> (ByteString -> Either CryptoError SecretKey) -> ByteString -> io SecretKey forall b c a. (b -> c) -> (a -> b) -> a -> c . (SecretKey -> SecretKey) -> Either CryptoError SecretKey -> Either CryptoError SecretKey forall a b. (a -> b) -> Either CryptoError a -> Either CryptoError b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap SecretKey -> SecretKey SecretKey.MkSecretKey (Either CryptoError SecretKey -> Either CryptoError SecretKey) -> (ByteString -> Either CryptoError SecretKey) -> ByteString -> Either CryptoError SecretKey forall b c a. (b -> c) -> (a -> b) -> a -> c . CryptoFailable SecretKey -> Either CryptoError SecretKey forall a. CryptoFailable a -> Either CryptoError a Error.eitherCryptoError (CryptoFailable SecretKey -> Either CryptoError SecretKey) -> (ByteString -> CryptoFailable SecretKey) -> ByteString -> Either CryptoError SecretKey forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> CryptoFailable SecretKey forall ba. ByteArrayAccess ba => ba -> CryptoFailable SecretKey Ed25519.secretKey (ByteString -> io SecretKey) -> ByteString -> io SecretKey forall a b. (a -> b) -> a -> b $ String -> ByteString Ascii.pack String "ABCDEFGHIJKLMNOPQRSTUVWXYZ012345" Test.assertEq test (SecretKey.render secretKey) (Ascii.pack "whsk_QUJDREVGR0hJSktMTU5PUFFSU1RVVldYWVowMTIzNDU=")