Skip to content

Commit

Permalink
Add unsafeMkSomeMnemonicFromEntropy, unsafeMkEntropy + misc
Browse files Browse the repository at this point in the history
  • Loading branch information
Anviking committed Feb 14, 2020
1 parent 922eed3 commit 00a9f80
Show file tree
Hide file tree
Showing 8 changed files with 96 additions and 34 deletions.
1 change: 1 addition & 0 deletions lib/core/src/Cardano/Wallet/Primitive/Mnemonic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,7 @@ module Cardano.Wallet.Primitive.Mnemonic
, MnemonicWordsError(..)
, ValidEntropySize
, ValidChecksumSize
, ValidMnemonicSentence
, ConsistentEntropy
, CheckSumBits
, EntropySize
Expand Down
45 changes: 44 additions & 1 deletion lib/core/src/Cardano/Wallet/Unsafe.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,8 @@ module Cardano.Wallet.Unsafe
, unsafeRunExceptT
, unsafeXPrv
, unsafeMkMnemonic
, unsafeMkEntropy
, unsafeSomeMnemonicFromEntropy
, unsafeDeserialiseCbor
, unsafeBech32DecodeFile
, unsafeBech32Decode
Expand All @@ -26,8 +28,21 @@ import Cardano.Crypto.Wallet
( XPrv )
import Cardano.Wallet.Api.Types
( DecodeAddress (..) )
import Cardano.Wallet.Primitive.AddressDerivation
( SomeMnemonic (..) )
import Cardano.Wallet.Primitive.Mnemonic
( ConsistentEntropy, EntropySize, Mnemonic, mkMnemonic )
( ConsistentEntropy
, Entropy
, EntropySize
, Mnemonic
, MnemonicWords
, ValidChecksumSize
, ValidEntropySize
, ValidMnemonicSentence
, entropyToMnemonic
, mkEntropy
, mkMnemonic
)
import Cardano.Wallet.Primitive.Types
( Address )
import Control.Monad
Expand All @@ -44,6 +59,8 @@ import Data.ByteString
( ByteString )
import Data.Char
( isHexDigit )
import Data.Proxy
( Proxy )
import Data.Text
( Text )
import Data.Text.Class
Expand Down Expand Up @@ -124,6 +141,32 @@ unsafeDeserialiseCbor decoder bytes = either
snd
(CBOR.deserialiseFromBytes decoder bytes)

unsafeMkEntropy
:: forall ent csz.
( HasCallStack
, ValidEntropySize ent
, ValidChecksumSize ent csz
)
=> ByteString
-> Entropy ent
unsafeMkEntropy = either (error . show) id . mkEntropy

unsafeSomeMnemonicFromEntropy
:: forall mw ent csz.
( HasCallStack
, ValidEntropySize ent
, ValidChecksumSize ent csz
, ValidMnemonicSentence mw
, ent ~ EntropySize mw
, mw ~ MnemonicWords ent
)
=> Proxy mw
-> ByteString
-> SomeMnemonic
unsafeSomeMnemonicFromEntropy _ = SomeMnemonic
. entropyToMnemonic
. unsafeMkEntropy @ent

-- | Load the data part of a bech32-encoded string from file. These files often
-- come from @jcli@. Only the first line of the file is read.
unsafeBech32DecodeFile :: HasCallStack => FilePath -> IO BL.ByteString
Expand Down
17 changes: 8 additions & 9 deletions lib/core/test/bench/db/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ import Cardano.Wallet.Primitive.AddressDiscovery.Sequential
, mkSeqState
)
import Cardano.Wallet.Primitive.Mnemonic
( EntropySize, entropyToMnemonic, genEntropy, mkEntropy )
( EntropySize, entropyToMnemonic, genEntropy )
import Cardano.Wallet.Primitive.Model
( Wallet, initWallet, unsafeInitWallet )
import Cardano.Wallet.Primitive.Types
Expand Down Expand Up @@ -100,7 +100,7 @@ import Cardano.Wallet.Primitive.Types
, fromFlatSlot
)
import Cardano.Wallet.Unsafe
( unsafeRunExceptT )
( unsafeRunExceptT, unsafeSomeMnemonicFromEntropy )
import Control.DeepSeq
( NFData (..), force )
import Control.Exception
Expand All @@ -122,6 +122,8 @@ import Data.ByteString
( ByteString )
import Data.Functor
( ($>) )
import Data.Proxy
( Proxy (..) )
import Data.Quantity
( Quantity (..) )
import Data.Time.Clock.System
Expand Down Expand Up @@ -611,9 +613,8 @@ initDummyState :: SeqState 'Testnet ShelleyKey
initDummyState =
mkSeqState (xprv, mempty) defaultAddressPoolGap
where
mnemonic = unsafePerformIO $
SomeMnemonic
. entropyToMnemonic @15
mnemonic = unsafePerformIO
$ SomeMnemonic . entropyToMnemonic @15
<$> genEntropy @(EntropySize 15)
xprv = generateKeyFromSeed (mnemonic, Nothing) mempty

Expand All @@ -634,14 +635,12 @@ testPk = PrimaryKey testWid
ourAccount :: ShelleyKey 'AccountK XPub
ourAccount = publicKey $ unsafeGenerateKeyFromSeed (seed, Nothing) mempty
where
seed = SomeMnemonic $ entropyToMnemonic @15 ent
ent = either (error . show) id $ mkEntropy $ BS.replicate 32 0
seed = unsafeSomeMnemonicFromEntropy (Proxy @15) (BS.replicate 32 0)

rewardAccount :: ShelleyKey 'AddressK XPub
rewardAccount = publicKey $ unsafeGenerateKeyFromSeed (seed, Nothing) mempty
where
seed = SomeMnemonic $ entropyToMnemonic @15 ent
ent = either (error . show) id $ mkEntropy $ BS.replicate 32 0
seed = unsafeSomeMnemonicFromEntropy (Proxy @15) (BS.replicate 32 0)

-- | Make a prefixed bytestring for use as a Hash or Address.
label :: Show n => String -> n -> B8.ByteString
Expand Down
13 changes: 8 additions & 5 deletions lib/core/test/unit/Cardano/Wallet/DB/Arbitrary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -149,6 +149,7 @@ import Test.QuickCheck
, arbitrarySizedBoundedIntegral
, choose
, elements
, frequency
, generate
, genericShrink
, liftArbitrary
Expand Down Expand Up @@ -466,11 +467,13 @@ rootKeysSeq = unsafePerformIO $ generate (vectorOf 10 genRootKeysSeq)
where
genRootKeysSeq :: Gen (ShelleyKey 'RootK XPrv)
genRootKeysSeq = do
(s, g, e) <- (,,)
<$> (SomeMnemonic <$> genMnemonic @12)
<*> (SomeMnemonic <$> genMnemonic @12)
<*> genPassphrase @"encryption" (0, 16)
return $ Seq.generateKeyFromSeed (s, Just g) e
s <- (SomeMnemonic <$> genMnemonic @12)
g <- frequency
[ (1, return Nothing)
, (3, Just . SomeMnemonic <$> genMnemonic @12)
]
e <- genPassphrase @"encryption" (0, 16)
return $ Seq.generateKeyFromSeed (s, g) e
{-# NOINLINE rootKeysSeq #-}

arbitrarySeqAccount
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -47,8 +47,12 @@ import Cardano.Wallet.Primitive.Mnemonic
( ConsistentEntropy, EntropySize, mkMnemonic )
import Cardano.Wallet.Primitive.Types
( Address )
import Cardano.Wallet.Unsafe
( unsafeSomeMnemonicFromEntropy )
import Control.Monad
( forM_ )
import Data.Proxy
( Proxy (..) )
import Data.Text
( Text )
import Test.Hspec
Expand All @@ -70,6 +74,20 @@ import qualified Data.Text as T
spec :: Spec
spec = do
describe "Golden Tests - Icarus' style addresses" $ do
let seed0 = unsafeSomeMnemonicFromEntropy (Proxy @15)
"4\175\242L\184\243\191 \169]\171 \207\r\v\233\NUL~&\ETB"

goldenAddressGeneration $ GoldenAddressGeneration
seed0 (toEnum 0x80000000) UTxOExternal (toEnum 0x00000000)
"Ae2tdPwUPEZGQVrA6qKreDzdtYxcWMMrpTFYCpFcuJfhJBEfoeiuW4MtaXZ"

goldenAddressGeneration $ GoldenAddressGeneration
seed0 (toEnum 0x80000000) UTxOExternal (toEnum 0x0000000E)
"Ae2tdPwUPEZDLWQQEBR1UW7HeXJVaqUnuw8DUFu52TDWCJbxbkCyQYyxckP"

goldenAddressGeneration $ GoldenAddressGeneration
seed0 (toEnum 0x8000000E) UTxOInternal (toEnum 0x0000002A)
"Ae2tdPwUPEZFRbyhz3cpfC2CumGzNkFBN2L42rcUc2yjQpEkxDbkPodpMAi"
let (Right seed1) = fromMnemonic @'[12]
[ "ghost", "buddy", "neutral", "broccoli", "face", "rack"
, "relief", "odor", "swallow", "real", "once", "ecology"
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -63,9 +63,11 @@ import Cardano.Wallet.Primitive.AddressDiscovery.Sequential
, shrinkPool
)
import Cardano.Wallet.Primitive.Mnemonic
( entropyToMnemonic, mkEntropy )
( entropyToMnemonic )
import Cardano.Wallet.Primitive.Types
( Address (..), ShowFmt (..) )
import Cardano.Wallet.Unsafe
( unsafeMkEntropy, unsafeSomeMnemonicFromEntropy )
import Control.Monad
( forM, forM_, unless )
import Control.Monad.IO.Class
Expand Down Expand Up @@ -344,7 +346,9 @@ prop_genChangeGap
prop_genChangeGap g =
property prop
where
Right mw = SomeMnemonic . entropyToMnemonic @12 <$> mkEntropy "0000000000000000"
mw = SomeMnemonic
$ entropyToMnemonic @12
$ unsafeMkEntropy "0000000000000000"
key = Shelley.unsafeGenerateKeyFromSeed (mw, Nothing) mempty
s0 = mkSeqState (key, mempty) g
prop =
Expand Down Expand Up @@ -378,7 +382,7 @@ prop_lookupDiscovered
prop_lookupDiscovered (s0, addr) =
let (ours, s) = isOurs addr s0 in ours ==> prop s
where
Right mw = SomeMnemonic . entropyToMnemonic @12 <$> mkEntropy "0000000000000000"
mw = unsafeSomeMnemonicFromEntropy (Proxy @12) "0000000000000000"
key = Shelley.unsafeGenerateKeyFromSeed (mw, Nothing) mempty
prop s = monadicIO $ liftIO $ do
unless (isJust $ isOwned s (key, mempty) addr) $ do
Expand Down Expand Up @@ -649,5 +653,5 @@ data Key = forall (k :: Depth -> * -> *).
instance Show Key where show (Key proxy) = show (typeRep proxy)

dummyMnemonic :: SomeMnemonic
dummyMnemonic = either (error . show) id $
SomeMnemonic . entropyToMnemonic @12 <$> mkEntropy (BS.pack $ replicate 16 0)
dummyMnemonic =
unsafeSomeMnemonicFromEntropy (Proxy @12) (BS.pack $ replicate 16 0)
12 changes: 4 additions & 8 deletions lib/core/test/unit/Cardano/Wallet/Primitive/TypesSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,11 +16,9 @@ module Cardano.Wallet.Primitive.TypesSpec
import Prelude

import Cardano.Wallet.Primitive.AddressDerivation
( Depth (..), SomeMnemonic (..), WalletKey (..), XPrv, digest, publicKey )
( Depth (..), WalletKey (..), XPrv, digest, publicKey )
import Cardano.Wallet.Primitive.AddressDerivation.Shelley
( ShelleyKey (..), generateKeyFromSeed )
import Cardano.Wallet.Primitive.Mnemonic
( entropyToMnemonic, mkEntropy )
import Cardano.Wallet.Primitive.Types
( ActiveSlotCoefficient (..)
, Address (..)
Expand Down Expand Up @@ -98,7 +96,7 @@ import Cardano.Wallet.Primitive.Types
, wholeRange
)
import Cardano.Wallet.Unsafe
( unsafeFromHex )
( unsafeFromHex, unsafeSomeMnemonicFromEntropy )
import Control.DeepSeq
( deepseq )
import Control.Exception
Expand Down Expand Up @@ -214,10 +212,8 @@ spec = do

describe "Buildable" $ do
it "WalletId" $ do
let mw = either (error . show) id
$ SomeMnemonic
. entropyToMnemonic @12
<$> mkEntropy "0000000000000000"
let mw = unsafeSomeMnemonicFromEntropy (Proxy @12)
"0000000000000000"
let xprv = generateKeyFromSeed
(mw, Nothing) mempty :: ShelleyKey 'RootK XPrv
let wid = WalletId $ digest $ publicKey xprv
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ import Cardano.Wallet.Primitive.AddressDerivation.Shelley
import Cardano.Wallet.Primitive.CoinSelection
( CoinSelection (..) )
import Cardano.Wallet.Primitive.Mnemonic
( EntropySize, entropyToMnemonic, mkEntropy )
( EntropySize )
import Cardano.Wallet.Primitive.Types
( Address (..)
, Coin (..)
Expand All @@ -47,7 +47,7 @@ import Cardano.Wallet.Primitive.Types
import Cardano.Wallet.Transaction
( ErrMkTx (..), TransactionLayer (..) )
import Cardano.Wallet.Unsafe
( unsafeFromHex )
( unsafeFromHex, unsafeSomeMnemonicFromEntropy )
import Data.ByteArray.Encoding
( Base (Base16), convertToBase )
import Data.ByteString
Expand Down Expand Up @@ -537,8 +537,7 @@ xprvSeqFromSeed bytes =
)
where
pwd = mempty
seed = SomeMnemonic $ entropyToMnemonic @12 ent
ent = either (error . show) id $ mkEntropy @(EntropySize 12) bytes
seed = unsafeSomeMnemonicFromEntropy (Proxy @(EntropySize 12)) bytes

xprvRndFromSeed
:: ByteString
Expand All @@ -550,8 +549,7 @@ xprvRndFromSeed bytes =
where
pwd = mempty
derPath = (minBound, minBound)
seed = SomeMnemonic $ entropyToMnemonic ent
ent = either (error . show) id $ mkEntropy @(EntropySize 12) bytes
seed = unsafeSomeMnemonicFromEntropy (Proxy @(EntropySize 12)) bytes

mkKeystore :: Ord k => [(k,v)] -> (k -> Maybe v)
mkKeystore pairs k =
Expand Down

0 comments on commit 00a9f80

Please sign in to comment.