{-# LANGUAGE DataKinds #-} module Cardano.Wallet.Primitive.Passphrase.Gen ( genUserPassphrase , shrinkUserPassphrase , genPassphraseScheme , genEncryptionPassphrase ) where import Prelude import Cardano.Wallet.Primitive.Passphrase ( Passphrase (..) , PassphraseMaxLength (..) , PassphraseMinLength (..) , PassphraseScheme (..) , preparePassphrase ) import Control.Monad ( replicateM ) import Data.Proxy ( Proxy (..) ) import Test.QuickCheck ( Gen, arbitraryPrintableChar, choose ) import Test.QuickCheck.Arbitrary.Generic ( genericArbitrary ) import qualified Data.ByteArray as BA import qualified Data.ByteString.Char8 as B8 import qualified Data.Text as T import qualified Data.Text.Encoding as T genUserPassphrase :: Gen (Passphrase "user") genUserPassphrase :: Gen (Passphrase "user") genUserPassphrase = do Int n <- (Int, Int) -> Gen Int forall a. Random a => (a, a) -> Gen a choose (Proxy "user" -> Int forall (purpose :: Symbol). PassphraseMinLength purpose => Proxy purpose -> Int passphraseMinLength Proxy "user" p, Proxy "user" -> Int forall (purpose :: Symbol). PassphraseMaxLength purpose => Proxy purpose -> Int passphraseMaxLength Proxy "user" p) ByteString bytes <- Text -> ByteString T.encodeUtf8 (Text -> ByteString) -> (String -> Text) -> String -> ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Text T.pack (String -> ByteString) -> Gen String -> Gen ByteString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Int -> Gen Char -> Gen String forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a] replicateM Int n Gen Char arbitraryPrintableChar Passphrase "user" -> Gen (Passphrase "user") forall (m :: * -> *) a. Monad m => a -> m a return (Passphrase "user" -> Gen (Passphrase "user")) -> Passphrase "user" -> Gen (Passphrase "user") forall a b. (a -> b) -> a -> b $ ScrubbedBytes -> Passphrase "user" forall (purpose :: Symbol). ScrubbedBytes -> Passphrase purpose Passphrase (ScrubbedBytes -> Passphrase "user") -> ScrubbedBytes -> Passphrase "user" forall a b. (a -> b) -> a -> b $ ByteString -> ScrubbedBytes forall bin bout. (ByteArrayAccess bin, ByteArray bout) => bin -> bout BA.convert ByteString bytes where p :: Proxy "user" p = Proxy "user" forall k (t :: k). Proxy t Proxy :: Proxy "user" shrinkUserPassphrase :: Passphrase "user" -> [Passphrase "user"] shrinkUserPassphrase :: Passphrase "user" -> [Passphrase "user"] shrinkUserPassphrase (Passphrase ScrubbedBytes bytes) | ScrubbedBytes -> Int forall ba. ByteArrayAccess ba => ba -> Int BA.length ScrubbedBytes bytes Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <= Proxy "user" -> Int forall (purpose :: Symbol). PassphraseMinLength purpose => Proxy purpose -> Int passphraseMinLength Proxy "user" p = [] | Bool otherwise = [ ScrubbedBytes -> Passphrase "user" forall (purpose :: Symbol). ScrubbedBytes -> Passphrase purpose Passphrase (ScrubbedBytes -> Passphrase "user") -> ScrubbedBytes -> Passphrase "user" forall a b. (a -> b) -> a -> b $ ByteString -> ScrubbedBytes forall bin bout. (ByteArrayAccess bin, ByteArray bout) => bin -> bout BA.convert (ByteString -> ScrubbedBytes) -> ByteString -> ScrubbedBytes forall a b. (a -> b) -> a -> b $ Int -> ByteString -> ByteString B8.take (Proxy "user" -> Int forall (purpose :: Symbol). PassphraseMinLength purpose => Proxy purpose -> Int passphraseMinLength Proxy "user" p) (ByteString -> ByteString) -> ByteString -> ByteString forall a b. (a -> b) -> a -> b $ ScrubbedBytes -> ByteString forall bin bout. (ByteArrayAccess bin, ByteArray bout) => bin -> bout BA.convert ScrubbedBytes bytes ] where p :: Proxy "user" p = Proxy "user" forall k (t :: k). Proxy t Proxy :: Proxy "user" genPassphraseScheme :: Gen PassphraseScheme genPassphraseScheme :: Gen PassphraseScheme genPassphraseScheme = Gen PassphraseScheme forall a (ga :: * -> *) (some :: Bool). (Generic a, GArbitrary a ga some, ga ~ Rep a) => Gen a genericArbitrary genEncryptionPassphrase :: Gen (Passphrase "encryption") genEncryptionPassphrase :: Gen (Passphrase "encryption") genEncryptionPassphrase = PassphraseScheme -> Passphrase "user" -> Passphrase "encryption" preparePassphrase PassphraseScheme EncryptWithPBKDF2 (Passphrase "user" -> Passphrase "encryption") -> Gen (Passphrase "user") -> Gen (Passphrase "encryption") forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen (Passphrase "user") genUserPassphrase