Skip to content

Commit

Permalink
Add Signing module with mkStdTx
Browse files Browse the repository at this point in the history
  • Loading branch information
Anviking committed Apr 10, 2019
1 parent 640abe6 commit 85b9547
Show file tree
Hide file tree
Showing 4 changed files with 146 additions and 6 deletions.
1 change: 1 addition & 0 deletions cardano-wallet.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -81,6 +81,7 @@ library
Cardano.Wallet.Primitive.Mnemonic
Cardano.Wallet.Primitive.Model
Cardano.Wallet.Primitive.Types
Cardano.Wallet.Primitive.Signing
Data.Text.Class
Data.Quantity
Servant.Extra.ContentTypes
Expand Down
8 changes: 4 additions & 4 deletions src/Cardano/Wallet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -61,6 +61,8 @@ import Cardano.Wallet.Primitive.AddressDiscovery
( AddressPoolGap, SeqState (..), mkAddressPool )
import Cardano.Wallet.Primitive.Model
( Wallet, applyBlocks, availableUTxO, getState, initWallet )
import Cardano.Wallet.Primitive.Signing
( mkStdTx )
import Cardano.Wallet.Primitive.Types
( Block (..)
, SignedTx (..)
Expand Down Expand Up @@ -239,12 +241,12 @@ mkWalletLayer db network = WalletLayer
let signed = SignedTx $ toByteString $ encodeSignedTx (tx, witnesses)
withExceptT NetworkError $ postTx network signed

, signTx = \wid rootXPrv password (CoinSelection ins outs chgs) -> do
, signTx = \wid rootXPrv password (CoinSelection ins outs _chgs) -> do
(w, _) <- withExceptT ErrSignTxNoSuchWallet $ _readWallet wid
maybe
(throwE ErrSignTx)
return
(mkStdTx (getState w) rootXPrv password ins outs chgs)
(mkStdTx (getState w) (rootXPrv, password) ins outs)

{---------------------------------------------------------------------------
W.I.P. / Debts
Expand Down Expand Up @@ -289,8 +291,6 @@ mkWalletLayer db network = WalletLayer
unsafeRunExceptT $ DB.putCheckpoint db (PrimaryKey wid) cp'
unsafeRunExceptT $ DB.putTxHistory db (PrimaryKey wid) txs

mkStdTx = error "TODO: mkStdTx not implemented yet"

{-------------------------------------------------------------------------------
Helpers
-------------------------------------------------------------------------------}
Expand Down
58 changes: 56 additions & 2 deletions src/Cardano/Wallet/Primitive/AddressDerivation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ module Cardano.Wallet.Primitive.AddressDerivation
, digest
, XPub
, XPrv
, encodeXPub

-- * Passphrase
, Passphrase(..)
Expand All @@ -49,6 +50,10 @@ module Cardano.Wallet.Primitive.AddressDerivation
, deriveAddressPrivateKey
, deriveAddressPublicKey
, keyToAddress

-- * Signing
, sign
, SignTag (..)
) where

import Prelude
Expand All @@ -64,7 +69,7 @@ import Cardano.Crypto.Wallet
, unXPub
)
import Cardano.Wallet.Binary
( encodeAddress )
( encodeAddress, toByteString )
import Cardano.Wallet.Primitive.Mnemonic
( CheckSumBits
, ConsistentEntropy
Expand All @@ -74,7 +79,7 @@ import Cardano.Wallet.Primitive.Mnemonic
, mnemonicToEntropy
)
import Cardano.Wallet.Primitive.Types
( Address (..) )
( Address (..), Hash (..) )
import Control.Arrow
( left )
import Control.DeepSeq
Expand All @@ -85,6 +90,8 @@ import Data.Bifunctor
( first )
import Data.ByteArray
( ScrubbedBytes )
import Data.ByteString
( ByteString )
import Data.Maybe
( fromMaybe )
import Data.Proxy
Expand All @@ -102,6 +109,7 @@ import GHC.Generics
import GHC.TypeLits
( Nat, Symbol )

import qualified Cardano.Crypto.Wallet as CC
import qualified Codec.CBOR.Encoding as CBOR
import qualified Codec.CBOR.Write as CBOR
import qualified Data.ByteArray as BA
Expand Down Expand Up @@ -188,6 +196,11 @@ digest
digest (Key xpub) =
hash (unXPub xpub)

-- | Get the underlying ByteString
encodeXPub :: (Key level XPub) -> ByteString
encodeXPub (Key k) = unXPub k


{-------------------------------------------------------------------------------
Passphrases
-------------------------------------------------------------------------------}
Expand Down Expand Up @@ -483,3 +496,44 @@ keyToAddress (Key xpub) =
-- let accXPub :: Key 'AccountL XPub
-- accXPub = publicKey $ deriveAccountPrivateKey mempty rootXPrv accIx
-- @


{-------------------------------------------------------------------------------
Signing
-------------------------------------------------------------------------------}

-- | Used for signing transactions
sign
:: SignTag
-> (Key 'AddressK XPrv, Passphrase "encryption")
-> Hash "signature"
sign tag (Key k, (Passphrase pwd)) =
Hash . CC.unXSignature $ CC.sign pwd k (signTag tag)


-- | To protect agains replay attacks (i.e. when an attacker intercepts a
-- signed piece of data and later sends it again), we add a tag to all data
-- that we sign. This ensures that even if some bytestring can be
-- deserialized into two different types of messages (A and B), the attacker
-- can't take message A and send it as message B.
--
-- We also automatically add the network tag ('protocolMagic') whenever it
-- makes sense, to ensure that things intended for testnet won't work for
-- mainnet.
--
-- The wallet only cares about the 'SignTx' tag. In 'cardano-sl' there was
-- a lot more cases.
newtype SignTag
= SignTx (Hash "tx")
deriving (Eq, Ord, Show, Generic)


-- | Encode magic bytes & the contents of a @SignTag@. Magic bytes are
-- guaranteed to be different (and begin with a different byte) for different
-- tags.
signTag :: SignTag -> ByteString
signTag = \case
SignTx (Hash payload) -> "\x01" <> network <> payload
where
network = toByteString . CBOR.encodeInt32 $ pm
pm = error "TODO: we need to decide on how we want to pass this in"
85 changes: 85 additions & 0 deletions src/Cardano/Wallet/Primitive/Signing.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,85 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}
module Cardano.Wallet.Primitive.Signing where

import Prelude

import Cardano.Wallet.Binary
( TxWitness (..), encodeTx, toByteString )
import Cardano.Wallet.Primitive.AddressDerivation
( ChangeChain (ExternalChain)
, Depth (AddressK, RootK)
, Key
, Passphrase
, SignTag (SignTx)
, XPrv
, deriveAccountPrivateKey
, deriveAddressPrivateKey
, encodeXPub
, publicKey
, sign
)
import Cardano.Wallet.Primitive.AddressDiscovery
( SeqState (externalPool), lookupAddress )
import Cardano.Wallet.Primitive.Types
( Address, Hash (..), Tx (..), TxIn, TxOut (..) )
import Control.Monad
( forM )
import Crypto.Hash
( Blake2b_256, hash )
import Data.ByteArray
( convert )
import Data.ByteString
( ByteString )

-- | Build a transaction

-- | Construct a standard transaction
--
-- " Standard " here refers to the fact that we do not deal with redemption,
-- multisignature transactions, etc.
--
-- TODO: re-add shuffle
-- TODO: I removed FakeSigner/SafeSigner. Might be wrong.
mkStdTx :: SeqState
-> (Key 'RootK XPrv, Passphrase "encryption")
-> [(TxIn, TxOut)]
-- ^ Selected inputs
-> [TxOut]
-- ^ Selected outputs (including change)
-> Maybe (Tx, [TxWitness])
mkStdTx seqState (rootPrv, pwd) ownedIns outs = do

let ins = (fmap fst ownedIns)
tx = Tx ins outs
txSigData = hashTx tx

txWitness <- forM ownedIns (\(_in, TxOut addr _c) -> mkWitness txSigData <$> keyFrom addr)

return (tx, txWitness)

where
hashTx :: Tx -> Hash "tx"
hashTx tx = Hash
$ convert
$ (hash @ByteString @Blake2b_256)
$ toByteString
$ encodeTx tx

keyFrom :: Address -> (Maybe (Key 'AddressK XPrv))
keyFrom addr = do
-- We are assuming there is only one account
let account = minBound
let accountPrv = deriveAccountPrivateKey pwd rootPrv account

-- We are ignoring the new state/pool. We won't discover any new
-- addresses when submitting transactions.
index <- fst $ lookupAddress addr (externalPool seqState)

return $ deriveAddressPrivateKey pwd accountPrv ExternalChain index

mkWitness :: Hash "tx" -> Key 'AddressK XPrv -> TxWitness
mkWitness tx xPrv =
PublicKeyWitness $
encodeXPub (publicKey xPrv) <>
getHash (sign (SignTx tx) (xPrv, pwd))

0 comments on commit 85b9547

Please sign in to comment.