Skip to content

Commit

Permalink
[ADP-3215] Add TxId type to Cardano.Wallet.Read (#4619)
Browse files Browse the repository at this point in the history
This pull request adds a type `TxId` to the `Read` hierarchy, and also
starts to split the hierarchy into two parts:

* `Cardano.Read.Ledger` — presents an era-indexed interface to the
ledger types
* `Cardano.Wallet.Read` — uses the above types to present a
self-contained, era-indexed and hopefully simple view of the ledger
concepts.

### Comments

On `Cardano.Read.Ledger`:

* I have refrained from renaming the existing modules in
`Cardano.Wallet.Read` — I intend to move them later.

On `Cardano.Wallet.Read`:

* The `TxId` type is era-_independent_: A `TxId` that was parsed in one
`era` may refer to a transaction which is from an entirely different
era, and we can't even statically tell from which one. Hence, the type
has no `era`-parameter.
* For the internal representation of `TxId`, I have chosen to be
compatible with the type `TxId` from the shelley-style ledgers with
zero-cost conversion. For Byron-transactions we do need to convert,
though.
* This pull request prepares the addition of a `TxIn` type.

### Issue Number

ADP-3215
  • Loading branch information
HeinrichApfelmus authored Jul 26, 2024
2 parents a3ff16c + 5728b62 commit 86a5557
Show file tree
Hide file tree
Showing 15 changed files with 514 additions and 31 deletions.
3 changes: 3 additions & 0 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -269,6 +269,9 @@ package cardano-wallet-network-layer
package cardano-wallet-primitive
tests: True

package cardano-wallet-read
tests: True

package cardano-wallet-text-class
tests: True

Expand Down
4 changes: 4 additions & 0 deletions lib/read/cardano-wallet-read.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,8 @@ flag release
library
import: opts-lib, language
exposed-modules:
Cardano.Read.Ledger
Cardano.Read.Ledger.Tx.TxId
Cardano.Wallet.Read
Cardano.Wallet.Read.Block
Cardano.Wallet.Read.Block.BHeader
Expand Down Expand Up @@ -90,6 +92,7 @@ library
Cardano.Wallet.Read.Tx.Outputs
Cardano.Wallet.Read.Tx.ReferenceInputs
Cardano.Wallet.Read.Tx.ScriptValidity
Cardano.Wallet.Read.Tx.TxId
Cardano.Wallet.Read.Tx.Validity
Cardano.Wallet.Read.Tx.Withdrawals
Cardano.Wallet.Read.Tx.Witnesses
Expand Down Expand Up @@ -147,6 +150,7 @@ test-suite test
other-modules:
Cardano.Wallet.Read.EraValueSpec
Cardano.Wallet.Read.Tx.CBORSpec
Cardano.Wallet.Read.Tx.TxIdSpec
Spec
SpecHook

Expand Down
25 changes: 25 additions & 0 deletions lib/read/lib/Cardano/Read/Ledger.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
{- |
Copyright: © 2024 Cardano Foundation
License: Apache-2.0
The module hierarchy "Cardano.Read.Ledger" contains data types
that are used for reading from the Cardano mainnet ledger.
Specifically, these data types are represented as
era-indexed unions of types from the Haskell ledger implementations
that are used in `cardano-node`.
"Cardano.Read.Ledger" is meant to
* Provide an era-indexed interface over the Byron and Shelley-style
ledger implementations.
* Improve the useability of type classes in the Shelley-style ledger
implementation with explicitly notated instances
and specialization to single eras.
In contrast, the module hierarchy "Cardano.Wallet.Read"
is meant to provide a semantic view of the ledger,
such that the implementation of this view is built on
and mostly compatible with "Cardano.Read.Ledger".
-}
module Cardano.Read.Ledger where
84 changes: 84 additions & 0 deletions lib/read/lib/Cardano/Read/Ledger/Tx/TxId.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,84 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}

-- |
-- Copyright: © 2024 Cardano Foundation
-- License: Apache-2.0
--
module Cardano.Read.Ledger.Tx.TxId
( TxIdType
, TxId (..)
, getEraTxId
)
where

import Prelude

import Cardano.Chain.UTxO
( taTx
)
import Cardano.Crypto.Hashing
( serializeCborHash
)
import Cardano.Ledger.Core
( bodyTxL
, txIdTxBody
)
import Cardano.Ledger.Crypto
( StandardCrypto
)
import Cardano.Wallet.Read
( Tx
)
import Cardano.Wallet.Read.Eras
( Allegra
, Alonzo
, Babbage
, Byron
, Conway
, Era (..)
, IsEra (..)
, Mary
, Shelley
)
import Cardano.Wallet.Read.Tx.Eras
( onTx
)
import Control.Lens
( (^.)
)

import qualified Cardano.Chain.UTxO as BY
import qualified Cardano.Ledger.Core as SH.Core
import qualified Cardano.Ledger.TxIn as SH.TxIn

type family TxIdType era where
TxIdType Byron = BY.TxId
TxIdType Shelley = SH.TxIn.TxId StandardCrypto
TxIdType Allegra = SH.TxIn.TxId StandardCrypto
TxIdType Mary = SH.TxIn.TxId StandardCrypto
TxIdType Alonzo = SH.TxIn.TxId StandardCrypto
TxIdType Babbage = SH.TxIn.TxId StandardCrypto
TxIdType Conway = SH.TxIn.TxId StandardCrypto

newtype TxId era = TxId {unTxId :: TxIdType era}

{-# INLINEABLE getEraTxId #-}
getEraTxId :: forall era. IsEra era => Tx era -> TxId era
getEraTxId = case theEra :: Era era of
Byron -> TxId . onTx byronTxId
Shelley -> TxId . onTx shelleyTxId
Allegra -> TxId . onTx shelleyTxId
Mary -> TxId . onTx shelleyTxId
Alonzo -> TxId . onTx shelleyTxId
Babbage -> TxId . onTx shelleyTxId
Conway -> TxId . onTx shelleyTxId

byronTxId :: BY.ATxAux a -> BY.TxId
byronTxId = serializeCborHash . taTx

shelleyTxId
:: SH.Core.EraTx era
=> SH.Core.Tx era
-> SH.TxIn.TxId (SH.Core.EraCrypto era)
shelleyTxId tx = txIdTxBody (tx ^. bodyTxL)
21 changes: 14 additions & 7 deletions lib/read/lib/Cardano/Wallet/Read/Block/Gen/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -73,11 +73,12 @@ import Cardano.Wallet.Read.Tx.Gen.TxParameters
( Address (..)
, Index (..)
, Lovelace (..)
, TxId (..)
, TxParameters (..)
)
import Cardano.Wallet.Read.Tx.Hash
( getEraTxHash
import Cardano.Wallet.Read.Tx.TxId
( TxId
, getTxId
, txIdFromHash
)
import Control.Category
( (.)
Expand Down Expand Up @@ -118,6 +119,9 @@ import Data.Kind
import Data.List.NonEmpty
( NonEmpty (..)
)
import Data.Maybe
( fromJust
)
import Data.Monoid
( Endo (..)
)
Expand All @@ -136,6 +140,7 @@ import Test.QuickCheck.Random
( mkQCGen
)

import qualified Cardano.Wallet.Read.Hash as Hash
import qualified Data.ByteString.Char8 as B8

-- | DSL for building a tx
Expand Down Expand Up @@ -267,8 +272,8 @@ interpretChainF m genAddress blockNo ml = do
-> BlockParameters era
-> ChainM m a
updateCurrentBlock k newTx bp =
let txid' = getEraTxHash newTx
in interpretChainF (k $ TxId txid') genAddress blockNo
let txid' = getTxId newTx
in interpretChainF (k txid') genAddress blockNo
$ Just
$ CurrentBlockParameters
$ over txsL (newTx :) bp
Expand Down Expand Up @@ -389,11 +394,13 @@ exampleChainF = do

-- Generate an invalid (not an hash) txid from a char
txid :: Char -> TxId
txid = TxId . B8.pack . replicate 32
txid = txIdFromHash . fromJust . Hash.hashFromBytes . B8.pack . replicate 32

-- Generate a random invalid txid
genTxId :: Gen TxId
genTxId = TxId . B8.pack <$> replicateM 32 (choose ('a', 'z'))
genTxId =
txIdFromHash . fromJust . Hash.hashFromBytes . B8.pack
<$> replicateM 32 (choose ('a', 'z'))

-- an infinite list of example blocks computed out of repeating the 'exampleChainF'
exampleBlocks :: [ConsensusBlock]
Expand Down
4 changes: 3 additions & 1 deletion lib/read/lib/Cardano/Wallet/Read/Tx/Gen/Allegra.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,10 +38,12 @@ import Cardano.Wallet.Read.Tx.Gen.TxParameters
( Address (..)
, Index (..)
, Lovelace (..)
, TxId (..)
, TxParameters (..)
, exampleTxParameters
)
import Cardano.Wallet.Read.Tx.TxId
( TxId
)
import Data.List.NonEmpty
( NonEmpty
)
Expand Down
4 changes: 3 additions & 1 deletion lib/read/lib/Cardano/Wallet/Read/Tx/Gen/Alonzo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,10 +62,12 @@ import Cardano.Wallet.Read.Tx.Gen.TxParameters
( Address (..)
, Index (..)
, Lovelace (..)
, TxId (..)
, TxParameters (..)
, exampleTxParameters
)
import Cardano.Wallet.Read.Tx.TxId
( TxId
)
import Data.Foldable
( toList
)
Expand Down
4 changes: 3 additions & 1 deletion lib/read/lib/Cardano/Wallet/Read/Tx/Gen/Babbage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -79,10 +79,12 @@ import Cardano.Wallet.Read.Tx.Gen.TxParameters
( Address (..)
, Index (..)
, Lovelace (..)
, TxId (..)
, TxParameters (..)
, exampleTxParameters
)
import Cardano.Wallet.Read.Tx.TxId
( TxId
)
import Data.Foldable
( toList
)
Expand Down
19 changes: 12 additions & 7 deletions lib/read/lib/Cardano/Wallet/Read/Tx/Gen/Byron.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,10 +33,13 @@ import Cardano.Wallet.Read.Tx.Gen.TxParameters
( Address (..)
, Index (..)
, Lovelace (..)
, TxId (..)
, TxParameters (..)
, exampleTxParameters
)
import Cardano.Wallet.Read.Tx.TxId
( TxId
, hashFromTxId
)
import Data.ByteString
( ByteString
)
Expand All @@ -50,6 +53,7 @@ import GHC.Stack
import qualified Cardano.Chain.Common as Byron
import qualified Cardano.Chain.UTxO as Byron
import qualified Cardano.Crypto.Signing as Byron
import qualified Cardano.Wallet.Read.Hash as Hash

mkByronTx
:: HasCallStack
Expand All @@ -64,8 +68,8 @@ mkByronTx TxParameters{txInputs, txOutputs} =
outputs = txOutputs <&> mkByronTxOut

mkByronInput :: (Index, TxId) -> TxIn
mkByronInput (Index idx, TxId h) =
TxInUtxo (hashUnsafe h)
mkByronInput (Index idx, txid) =
TxInUtxo (unsafeHashFromTxId txid)
$ fromIntegral idx

mkByronTxOut :: HasCallStack => (Address, Lovelace) -> Byron.TxOut
Expand All @@ -88,10 +92,11 @@ mkByronAddrFromXPub addr =
(Byron.VerKeyASD $ Byron.VerificationKey $ XPub addr $ ChainCode mempty)
$ Byron.AddrAttributes Nothing Byron.NetworkMainOrStage

hashUnsafe :: ByteString -> Hash a
hashUnsafe x = case hashFromBytes x of
Nothing -> error "hashUnsafe: failed to hash"
Just h -> h
unsafeHashFromTxId :: TxId -> Hash a
unsafeHashFromTxId txid =
case hashFromBytes (Hash.hashToBytes $ hashFromTxId txid) of
Nothing -> error "hashUnsafe: failed to hash"
Just h -> h

exampleByronTx :: ATxAux ()
exampleByronTx = mkByronTx exampleTxParameters
4 changes: 3 additions & 1 deletion lib/read/lib/Cardano/Wallet/Read/Tx/Gen/Conway.hs
Original file line number Diff line number Diff line change
Expand Up @@ -89,10 +89,12 @@ import Cardano.Wallet.Read.Tx.Gen.TxParameters
( Address (..)
, Index (..)
, Lovelace (..)
, TxId (..)
, TxParameters (..)
, exampleTxParameters
)
import Cardano.Wallet.Read.Tx.TxId
( TxId
)
import Data.Foldable
( toList
)
Expand Down
4 changes: 3 additions & 1 deletion lib/read/lib/Cardano/Wallet/Read/Tx/Gen/Mary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,10 +50,12 @@ import Cardano.Wallet.Read.Tx.Gen.TxParameters
( Address (..)
, Index (..)
, Lovelace (..)
, TxId (..)
, TxParameters (..)
, exampleTxParameters
)
import Cardano.Wallet.Read.Tx.TxId
( TxId
)
import Data.Foldable
( toList
)
Expand Down
12 changes: 5 additions & 7 deletions lib/read/lib/Cardano/Wallet/Read/Tx/Gen/Shelley.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,9 +50,6 @@ import Cardano.Ledger.Credential
import Cardano.Ledger.Keys
( KeyHash (..)
)
import Cardano.Ledger.SafeHash
( unsafeMakeSafeHash
)
import Cardano.Ledger.Shelley.API.Types
( ShelleyTx (ShelleyTx)
, ShelleyTxAuxData
Expand All @@ -78,10 +75,12 @@ import Cardano.Wallet.Read.Tx.Gen.TxParameters
( Address (..)
, Index (..)
, Lovelace (..)
, TxId (..)
, TxParameters (..)
, exampleTxParameters
)
import Cardano.Wallet.Read.Tx.TxId
( TxId
)
import Data.ByteString
( ByteString
)
Expand All @@ -107,7 +106,6 @@ import GHC.Stack
)

import qualified Cardano.Ledger.Core as L
import qualified Cardano.Ledger.TxIn as L
import qualified Data.ByteString.Short as B
import qualified Data.Set as Set

Expand Down Expand Up @@ -187,9 +185,9 @@ mkShelleyInput
=> Index
-> TxId
-> Set (TxIn StandardCrypto)
mkShelleyInput (Index idx) (TxId h) =
mkShelleyInput (Index idx) txid =
Set.singleton
$ mkTxInPartial (L.TxId $ unsafeMakeSafeHash $ UnsafeHash $ B.toShort h)
$ mkTxInPartial txid
$ fromIntegral idx

exampleShelleyTx :: ShelleyTx (ShelleyEra StandardCrypto)
Expand Down
Loading

0 comments on commit 86a5557

Please sign in to comment.