Skip to content

Commit

Permalink
implement jörmungandr txId
Browse files Browse the repository at this point in the history
  • Loading branch information
Anviking committed Jun 19, 2019
1 parent 8b659fb commit 24b1e35
Show file tree
Hide file tree
Showing 4 changed files with 74 additions and 10 deletions.
1 change: 1 addition & 0 deletions lib/jormungandr/cardano-wallet-jormungandr.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ library
, cardano-wallet-core
, cardano-crypto
, cborg
, cryptonite
, exceptions
, http-client
, http-types
Expand Down
10 changes: 6 additions & 4 deletions lib/jormungandr/src/Cardano/Wallet/Jormungandr/Binary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,8 @@ module Cardano.Wallet.Jormungandr.Binary
, getBlock
, getTransaction

, putTransaction
, putTokenTransfer
, putSignedTransaction

, ConfigParam (..)
, ConsensusVersion (..)
Expand All @@ -44,7 +45,8 @@ module Cardano.Wallet.Jormungandr.Binary
-- * Re-export
, runGet
, Get

, runPut
, Put
) where

import Prelude
Expand Down Expand Up @@ -234,8 +236,8 @@ getTransaction = label "getTransaction" $ do
error "unimplemented: Account witness"
other -> fail $ "Invalid witness type: " ++ show other

putTransaction :: (Tx, [TxWitness]) -> Put
putTransaction (tx, witnesses) = do
putSignedTransaction :: (Tx, [TxWitness]) -> Put
putSignedTransaction (tx, witnesses) = do
putTokenTransfer tx
mapM_ putWitness witnesses

Expand Down
24 changes: 22 additions & 2 deletions lib/jormungandr/src/Cardano/Wallet/Jormungandr/Compatibility.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,12 @@ module Cardano.Wallet.Jormungandr.Compatibility
import Prelude

import Cardano.Wallet.Jormungandr.Binary
( decodeLegacyAddress, singleAddressFromKey )
( Put
, decodeLegacyAddress
, putTokenTransfer
, runPut
, singleAddressFromKey
)
import Cardano.Wallet.Jormungandr.Environment
( KnownNetwork (..), Network (..) )
import Cardano.Wallet.Primitive.AddressDerivation
Expand All @@ -41,6 +46,10 @@ import Codec.Binary.Bech32
( HumanReadablePart, dataPartFromBytes, dataPartToBytes )
import Control.Monad
( when )
import Crypto.Hash
( hash )
import Crypto.Hash.Algorithms
( Blake2b_256 )
import Data.ByteString
( ByteString )
import Data.ByteString.Base58
Expand All @@ -53,8 +62,10 @@ import Data.Text.Class
( TextDecodingError (..) )

import qualified Codec.Binary.Bech32 as Bech32
import qualified Data.ByteArray as BA
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text.Encoding as T

-- | A type representing the Jormungandr as a network target. This has an
Expand All @@ -68,8 +79,17 @@ genesis = BlockHeader
, prevBlockHash = Hash (BS.replicate 32 0)
}

-- | Hash a transaction.
--
-- The corresponding rust implementation is:
-- https://github.com/input-output-hk/rust-cardano/blob/e5d974f7bedeb00c9c9d688ac66094a34bf8f40d/chain-impl-mockchain/src/transaction/transaction.rs#L115-L119
instance TxId (Jormungandr n) where
txId = undefined
txId = blake2b256 . putTokenTransfer
where
blake2b256 :: forall tag. Put -> Hash tag
blake2b256 =
Hash . BA.convert . hash @_ @Blake2b_256 . BL.toStrict . runPut


instance forall n. KnownNetwork n => KeyToAddress (Jormungandr n) where
keyToAddress key = singleAddressFromKey (Proxy @n) (getKey key)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@

module Cardano.Wallet.Jormungandr.CompatibilitySpec
( spec
) where
)where

import Prelude

Expand All @@ -22,9 +22,19 @@ import Cardano.Wallet.Jormungandr.Compatibility
import Cardano.Wallet.Jormungandr.Environment
( KnownNetwork (..), Network (..) )
import Cardano.Wallet.Primitive.Types
( Address (..), DecodeAddress (..), EncodeAddress (..), ShowFmt (..) )
( Address (..)
, Coin (..)
, DecodeAddress (..)
, EncodeAddress (..)
, Hash (..)
, ShowFmt (..)
, Tx (..)
, TxIn (..)
, TxOut (..)
, txId
)
import Data.ByteArray.Encoding
( Base (Base16), convertFromBase )
( Base (Base16), convertFromBase, convertToBase )
import Data.ByteString
( ByteString )
import Data.Proxy
Expand Down Expand Up @@ -52,7 +62,38 @@ import qualified Data.ByteString.Char8 as B8
import qualified Data.Text as T

spec :: Spec
spec = describe "EncodeAddress & DecodeAddress" $ do
spec = do
txIdSpec
addrSpec

txIdSpec :: Spec
txIdSpec = do
describe "txId @(Jormungandr n)" $ do
it "(txId largeTx) should match golden" $ do
toHex . getHash .txId @(Jormungandr 'Mainnet) $ largeTx
`shouldBe`
"872c2b8596956591554698e3877ac778e5fce0ea420f4b572d5a4cebc2a1c784"

it "(txId oneInOneOutTx) should match golden" $ do
toHex . getHash .txId @(Jormungandr 'Mainnet) $ oneInOneOutTx
`shouldBe`
"3f0b51696fc0d86f9d9949d53185bb3da0f7fa0e0440287061dcb121a0205e98"
where
toHex = convertToBase @ByteString @ByteString Base16
fromHex = either (error . show) id .
convertFromBase @ByteString @ByteString Base16

largeTx :: Tx
largeTx = Tx {inputs = [], outputs = [TxOut {address = Address {unAddress = "\131\&3$\195xi\193\"h\154\&5\145}\245:O\"\148\163\165/h^\ENQ\245\248\229;\135\231\234E/"}, coin = Coin {getCoin = 14}},TxOut {address = Address {unAddress = "\131\ENQK\186?\203{_$\145\134\ESCn+\139\240\163\249%|\223/\223A\202Z\247\a.w\199\SI:"}, coin = Coin {getCoin = 100000000000}},TxOut {address = Address {unAddress = "\131\147\147\196i\217\199\156^\"~z\242\228\"\136*\142.\188!l\221o\158T\224`\242\&1[\196\DC4"}, coin = Coin {getCoin = 100000000000}},TxOut {address = Address {unAddress = "\131\206\155\217\224f}\246\230\174y^\139\ACK\177\154\152=!\157\184\192&\v\175\204\239\215\RS\204\254\195\219"}, coin = Coin {getCoin = 100000000000}},TxOut {address = Address {unAddress = "\131\STX\NUL^\t\129\243\223Q={0\155\193\&0\250_Z|\167\244I\ETX\166]\189\165\188\147u\131\218="}, coin = Coin {getCoin = 100000000000}},TxOut {address = Address {unAddress = "\131\140\164,\SI\STX\170\195\SOH\145\ENQ\206\164\172\186n\194G\228\133\147\251\ENQX3%(\230 ~\209\188%"}, coin = Coin {getCoin = 100000000000}},TxOut {address = Address {unAddress = "\131\175\217\146d[\t\133\238>\174s[\168W\193\177\141W\173\246B\255\177r\145\137\191[Q\230\176\187"}, coin = Coin {getCoin = 100000000000}},TxOut {address = Address {unAddress = "\131\FS|T#\209X\a\236>\143S\DC1\169Ok/\181y\176g\182\212\DEL\167p\v\ETX\SOH\195c\t\160"}, coin = Coin {getCoin = 100000000000}},TxOut {address = Address {unAddress = "\131#c\211\176a\143T\204 \168\&3y\193fGM\209\DC2\FSgM\250\131I~1\236\197\SUB\148V\209"}, coin = Coin {getCoin = 100000000000}},TxOut {address = Address {unAddress = "\131\252\229\169j*u.n\159\184\CAN\214\203C2><\a&\191\140\202\150M\176\255\175\DLEFxZ!"}, coin = Coin {getCoin = 100000000000}},TxOut {address = Address {unAddress = "\131=K\138f\DC3\188x\154\144\173\DEL\241T\166\161\141Y\195\176\156\134\237;\146\173\232\250\&2\215\ACK@\254"}, coin = Coin {getCoin = 100000000000}}]}

oneInOneOutTx :: Tx
oneInOneOutTx = Tx
[TxIn (Hash $ fromHex "773955f8211e6b9d4ea723c7cc3ad2be12718a769d786b5077b03187bb0ceaa7") 2 ]
[TxOut (Address "\ETX\ENQK\186?\203{_$\145\134\ESCn+\139\240\163\249%|\223/\223A\202Z\247\a.w\199\SI:") (Coin 14000000)]


addrSpec :: Spec
addrSpec = describe "EncodeAddress & DecodeAddress" $ do
describe "Mainnet" $ do
let proxy = Proxy @(Jormungandr 'Mainnet)
let firstByteS = B8.unpack (BS.pack [single @'Mainnet])
Expand Down

0 comments on commit 24b1e35

Please sign in to comment.