From 7649fc29ace23e6142339177901237bfdcc71694 Mon Sep 17 00:00:00 2001 From: KtorZ Date: Wed, 6 Mar 2019 14:33:56 +0100 Subject: [PATCH] implement txId using CBOR encoders --- cardano-wallet.cabal | 2 ++ src/Cardano/Wallet/Binary.hs | 28 +++++++++++++++++++++++--- test/unit/Cardano/Wallet/BinarySpec.hs | 27 ++++++++++++++++++++++++- 3 files changed, 53 insertions(+), 4 deletions(-) diff --git a/cardano-wallet.cabal b/cardano-wallet.cabal index acaa3c6d47b..f4860279623 100644 --- a/cardano-wallet.cabal +++ b/cardano-wallet.cabal @@ -35,9 +35,11 @@ library , bytestring , cborg , containers + , cryptonite , deepseq , digest , transformers + , memory hs-source-dirs: src exposed-modules: diff --git a/src/Cardano/Wallet/Binary.hs b/src/Cardano/Wallet/Binary.hs index 6a1e1f2797f..1857c4af9e3 100644 --- a/src/Cardano/Wallet/Binary.hs +++ b/src/Cardano/Wallet/Binary.hs @@ -1,5 +1,6 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TypeApplications #-} -- | -- Copyright: © 2018-2019 IOHK @@ -16,9 +17,11 @@ module Cardano.Wallet.Binary -- * Decoding decodeBlock , decodeBlockHeader + , decodeTx -- * Encoding , encodeTx + , txId -- * Helpers , inspectNextToken @@ -40,6 +43,10 @@ import Cardano.Wallet.Primitive ) import Control.Monad ( void ) +import Crypto.Hash + ( hash ) +import Crypto.Hash.Algorithms + ( Blake2b_256 ) import Data.ByteString ( ByteString ) import Data.Digest.CRC32 @@ -55,6 +62,7 @@ import qualified Codec.CBOR.Decoding as CBOR import qualified Codec.CBOR.Encoding as CBOR import qualified Codec.CBOR.Read as CBOR import qualified Codec.CBOR.Write as CBOR +import qualified Data.ByteArray as BA import qualified Data.ByteString.Lazy as BL import qualified Data.Set as Set @@ -319,6 +327,16 @@ decodeSignature = do 2 -> decodeProxySignature decodeHeavyIndex _ -> fail $ "decodeSignature: unknown signature constructor: " <> show t +decodeSignedTx :: CBOR.Decoder s Tx +decodeSignedTx = do + _ <- CBOR.decodeListLenCanonicalOf 2 + _ <- CBOR.decodeListLenCanonicalOf 3 + ins <- decodeListIndef decodeTxIn + outs <- decodeListIndef decodeTxOut + _ <- decodeAttributes + _ <- decodeList decodeTxWitness + return $ Tx ins outs + decodeSharesProof :: CBOR.Decoder s () decodeSharesProof = do _ <- CBOR.decodeBytes -- Shares Hash @@ -341,16 +359,14 @@ decodeSoftwareVersion = do decodeTx :: CBOR.Decoder s Tx decodeTx = do - _ <- CBOR.decodeListLenCanonicalOf 2 _ <- CBOR.decodeListLenCanonicalOf 3 ins <- decodeListIndef decodeTxIn outs <- decodeListIndef decodeTxOut _ <- decodeAttributes - _ <- decodeList decodeTxWitness return $ Tx ins outs decodeTxPayload :: CBOR.Decoder s (Set Tx) -decodeTxPayload = Set.fromList <$> decodeListIndef decodeTx +decodeTxPayload = Set.fromList <$> decodeListIndef decodeSignedTx {-# ANN decodeTxIn ("HLint: ignore Use <$>" :: String) #-} decodeTxIn :: CBOR.Decoder s TxIn @@ -407,6 +423,12 @@ decodeUpdateProof = do -- * Encoding +-- | Compute a transaction id; assumed to be effectively injective. +-- It returns an hex-encoded 64-byte hash. +txId :: Tx -> Hash "Tx" +txId = + Hash . BA.convert . hash @_ @Blake2b_256 . CBOR.toStrictByteString . encodeTx + encodeAddressPayload :: ByteString -> CBOR.Encoding encodeAddressPayload payload = mempty <> CBOR.encodeListLen 2 diff --git a/test/unit/Cardano/Wallet/BinarySpec.hs b/test/unit/Cardano/Wallet/BinarySpec.hs index 3a0545b7350..171ecb9c77d 100644 --- a/test/unit/Cardano/Wallet/BinarySpec.hs +++ b/test/unit/Cardano/Wallet/BinarySpec.hs @@ -5,7 +5,7 @@ module Cardano.Wallet.BinarySpec (spec) where import Prelude import Cardano.Wallet.Binary - ( decodeBlock, decodeBlockHeader ) + ( decodeBlock, decodeBlockHeader, decodeTx, encodeTx, txId ) import Cardano.Wallet.Primitive ( Address (..) , Block (..) @@ -27,11 +27,13 @@ import Test.Hspec import qualified Codec.CBOR.Decoding as CBOR import qualified Codec.CBOR.Read as CBOR +import qualified Codec.CBOR.Write as CBOR import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy.Char8 as L8 import qualified Data.Set as Set +{-# ANN spec ("HLint: ignore Use head" :: String) #-} spec :: Spec spec = do describe "Decoding blocks" $ do @@ -55,6 +57,29 @@ spec = do let decoded = unsafeDeserialiseFromBytes decodeBlock bs decoded `shouldBe` block3 + describe "Encoding Tx" $ do + let txs = Set.toList (transactions block2 <> transactions block3) + let roundTripTx tx = do + let bytes = CBOR.toLazyByteString (encodeTx tx) + let tx' = unsafeDeserialiseFromBytes decodeTx bytes + tx `shouldBe` tx' + + it "encode . decode = pure (1)" $ do + roundTripTx (txs !! 0) + + it "encode . decode = pure (2)" $ do + roundTripTx (txs !! 1) + + it "should compute correct txId (1)" $ do + let hash = txId (txs !! 0) + let hash' = hash16 "c470563001e448e61ff1268c2a6eb458ace1d04011a02cb262b6d709d66c23d0" + hash `shouldBe` hash' + + it "should compute correct txId (2)" $ do + let hash = txId (txs !! 1) + let hash' = hash16 "d30d37f1f8674c6c33052826fdc5bc198e3e95c150364fd775d4bc663ae6a9e6" + hash `shouldBe` hash' + -- A mainnet block header blockHeader1 :: BlockHeader