Skip to content

Commit

Permalink
finish mkStdTx
Browse files Browse the repository at this point in the history
  • Loading branch information
paweljakubas committed Jul 3, 2020
1 parent 94f1f93 commit c77807c
Show file tree
Hide file tree
Showing 2 changed files with 34 additions and 12 deletions.
1 change: 1 addition & 0 deletions lib/shelley/cardano-wallet-shelley.cabal
Expand Up @@ -42,6 +42,7 @@ library
, cardano-config
, cardano-crypto
, cardano-crypto-class
, cardano-crypto-wrapper
, cardano-ledger
, cardano-slotting
, cardano-wallet-cli
Expand Down
45 changes: 33 additions & 12 deletions lib/shelley/src/Cardano/Wallet/Shelley/Transaction.hs
Expand Up @@ -43,7 +43,7 @@ import Cardano.Crypto.DSIGN
import Cardano.Crypto.DSIGN.Ed25519
( VerKeyDSIGN (..) )
import Cardano.Wallet.Primitive.AddressDerivation
( Depth (..), NetworkDiscriminant (..), Passphrase, WalletKey (..) )
( Depth (..), NetworkDiscriminant (..), Passphrase (..), WalletKey (..) )
import Cardano.Wallet.Primitive.AddressDerivation.Byron
( ByronKey )
import Cardano.Wallet.Primitive.AddressDerivation.Icarus
Expand Down Expand Up @@ -88,6 +88,8 @@ import Cardano.Wallet.Transaction
, ErrValidateSelection
, TransactionLayer (..)
)
import Control.Arrow
( second )
import Control.Monad
( forM )
import Crypto.Error
Expand All @@ -113,9 +115,11 @@ import Ouroboros.Network.Block

import qualified Cardano.Api as Cardano
import qualified Cardano.Byron.Codec.Cbor as CBOR
import qualified Cardano.Crypto as Byron
import qualified Cardano.Crypto.Hash.Class as Hash
import qualified Cardano.Crypto.Wallet as CC
import qualified Cardano.Wallet.Primitive.Types as W
import qualified Codec.CBOR.Encoding as CBOR
import qualified Codec.CBOR.Read as CBOR
import qualified Codec.CBOR.Write as CBOR
import qualified Crypto.PubKey.Ed25519 as Ed25519
Expand Down Expand Up @@ -156,7 +160,7 @@ newTransactionLayer
-> ProtocolMagic
-> EpochLength
-> TransactionLayer t k
newTransactionLayer _proxy _protocolMagic epochLength = TransactionLayer
newTransactionLayer _proxy protocolMagic epochLength = TransactionLayer
{ mkStdTx = _mkStdTx
, mkDelegationJoinTx = _mkDelegationJoinTx
, mkDelegationQuitTx = _mkDelegationQuitTx
Expand All @@ -173,7 +177,7 @@ newTransactionLayer _proxy _protocolMagic epochLength = TransactionLayer
-> [(TxIn, TxOut)]
-> [TxOut]
-> Either ErrMkTx (Tx, SealedTx)
_mkStdTx keyFrom slot ownedIns outs =case (txWitnessTagFor @k) of
_mkStdTx keyFrom slot ownedIns outs = case (txWitnessTagFor @k) of
TxWitnessShelleyUTxO -> do
let timeToLive = defaultTTL epochLength slot
let fee = realFee ownedIns outs
Expand All @@ -185,9 +189,32 @@ newTransactionLayer _proxy _protocolMagic epochLength = TransactionLayer
let wits = SL.WitnessSet addrWits mempty mempty
pure $ toSealed $ SL.Tx unsigned wits metadata
TxWitnessByronUTxO -> do
let Cardano.TxUnsignedByron unsigned _ _ =
mkUnsignedByronTx ownedIns outs
error "not implemented"
let (Cardano.TxUnsignedByron _ _ txHash) = mkUnsignedByronTx ownedIns outs
let tx = (fst <$> ownedIns, outs)
let sigData = Byron.hashToBytes txHash
witnesses <- forM ownedIns $ \(_, TxOut addr _) -> do
ks <- lookupPrivateKey keyFrom addr
pure $ mkByronWitness protocolMagic sigData ks
pure
( Tx (Hash sigData) (second coin <$> ownedIns) outs
, SealedTx $ CBOR.toStrictByteString $ CBOR.encodeSignedTx tx witnesses
)
where
mkByronWitness
:: ProtocolMagic
-> ByteString
-> (k 'AddressK XPrv, Passphrase "encryption")
-> ByteString
mkByronWitness (ProtocolMagic pm) sigData (xPrv, Passphrase pwd) =
CBOR.toStrictByteString
$ CBOR.encodePublicKeyWitness (getRawKey $ publicKey xPrv)
$ CC.unXSignature (CC.sign pwd (getRawKey xPrv) message)
where
message = mconcat
[ "\x01"
, CBOR.toStrictByteString (CBOR.encodeInt32 pm)
, CBOR.toStrictByteString (CBOR.encodeBytes sigData)
]

_mkDelegationJoinTx
:: FeePolicy
Expand Down Expand Up @@ -520,12 +547,6 @@ mkWitness body (prv, pwd) =
$ unsafeMkEd25519
$ toXPub prv

mkByronWitness
:: SL.TxBody TPraosStandardCrypto
-> (XPrv, Passphrase "encryption")
-> Cardano.TxWitness
mkByronWitness _ _ = undefined

signWith
:: ByteString
-> (XPrv, Passphrase "encryption")
Expand Down

0 comments on commit c77807c

Please sign in to comment.