Skip to content

Commit

Permalink
Add Cardano.Wallet.Read.Tx.TxOut
Browse files Browse the repository at this point in the history
  • Loading branch information
HeinrichApfelmus committed Aug 23, 2024
1 parent 3fcf8b3 commit 933b15f
Show file tree
Hide file tree
Showing 4 changed files with 466 additions and 9 deletions.
2 changes: 2 additions & 0 deletions lib/read/cardano-wallet-read.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -104,6 +104,7 @@ library
Cardano.Wallet.Read.Tx.ScriptValidity
Cardano.Wallet.Read.Tx.TxId
Cardano.Wallet.Read.Tx.TxIn
Cardano.Wallet.Read.Tx.TxOut
Cardano.Wallet.Read.Value

build-depends:
Expand Down Expand Up @@ -160,6 +161,7 @@ test-suite test
Cardano.Wallet.Read.EraValueSpec
Cardano.Wallet.Read.Tx.CBORSpec
Cardano.Wallet.Read.Tx.TxIdSpec
Cardano.Wallet.Read.Tx.TxOutSpec
Test.Unit.Cardano.Read.Ledger.Tx
Spec
SpecHook
Expand Down
304 changes: 304 additions & 0 deletions lib/read/lib/Cardano/Wallet/Read/Tx/TxOut.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,304 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}

{- |
Copyright: © 2024 Cardano Foundation
License: Apache-2.0
'TxOut' — transaction output.
-}
module Cardano.Wallet.Read.Tx.TxOut
( -- * TxOut
TxOut
, mkBasicTxOut
, getCompactAddr
, getValue
, utxoFromEraTx
, upgradeTxOutToBabbageOrLater

-- * Conversions
, toBabbageOutput
, toConwayOutput

-- * Serialization
, deserializeTxOut
, serializeTxOut

-- * Internal
, mkEraTxOut
)
where

import Prelude

import Cardano.Ledger.Binary
( DecoderError (DecoderErrorCustom)
)
import Cardano.Ledger.Compactible
( toCompact
)
import Cardano.Read.Ledger.Tx.CollateralOutputs
( CollateralOutputs (..)
, getEraCollateralOutputs
)
import Cardano.Read.Ledger.Tx.Output
( Output (..)
, OutputType
, deserializeOutput
, getEraCompactAddr
, getEraValue
, serializeOutput
, upgradeToOutputBabbage
, upgradeToOutputConway
)
import Cardano.Read.Ledger.Tx.Outputs
( Outputs (..)
, getEraOutputs
)
import Cardano.Wallet.Read.Address
( CompactAddr
, fromEraCompactAddr
)
import Cardano.Wallet.Read.Eras
( Babbage
, Conway
, Era (..)
, EraValue (..)
, IsEra (theEra)
, indexOfEra
, parseEraIndex
)
import Cardano.Wallet.Read.Tx
( Tx (..)
)
import Cardano.Wallet.Read.Tx.TxIn
( TxIn
, pattern TxIn
, pattern TxIx
)
import Cardano.Wallet.Read.Value
( Value
, fromEraValue
, toMaryValue
)
import Data.Foldable
( toList
)
import Data.Maybe
( fromMaybe
)
import Data.Maybe.Strict
( StrictMaybe (SNothing)
)
import Data.Word
( Word16
)

import qualified Cardano.Ledger.Babbage.TxBody as Babbage
import qualified Cardano.Wallet.Read.Tx.ScriptValidity as Read
import qualified Cardano.Wallet.Read.Tx.TxId as Read
import qualified Data.ByteString.Lazy as BL
import qualified Data.Map.Strict as Map
import qualified Data.Text as T

{-----------------------------------------------------------------------------
Type
------------------------------------------------------------------------------}
-- | A 'TxOut' is a transaction output from any era — past, present
-- or next one.
newtype TxOut = TxOutC (EraValue Output)

instance Show TxOut where
show (TxOutC v) = show v

-- | For testing — make a 'TxOut' from an era-indexed transaction output.
mkEraTxOut :: IsEra era => Output era -> TxOut
mkEraTxOut = TxOutC . EraValue

-- | Make a basic 'TxOut' from an address and a value.
mkBasicTxOut :: CompactAddr -> Value -> TxOut
mkBasicTxOut addr value =
TxOutC (EraValue (Output txout :: Output Conway))
where
val = toMaryValue value
-- The function 'toCompact' returns 'Nothing' when the input
-- contains quantities that are outside the bounds of a Word64,
-- x < 0 or x > (2^64 - 1)
-- Such quantities are valid 'Integer's, but they cannot be
-- encoded in a 'TxOut', hence the 'Nothing' result.
-- Cardano.Ledger uses the same error message when converting.
cVal = fromMaybe (error ("Illegal Value in TxOut: " ++ show val))
$ toCompact val
txout = Babbage.TxOutCompact addr cVal

{-# INLINEABLE getCompactAddr #-}
-- | Get the address which controls who can spend the transaction output.
getCompactAddr :: TxOut -> CompactAddr
getCompactAddr (TxOutC (EraValue txout)) =
fromEraCompactAddr $ getEraCompactAddr txout

{-# INLINEABLE getValue #-}
-- | Get the monetary 'Value' in this transaction output.
getValue :: TxOut -> Value
getValue (TxOutC (EraValue txout)) =
fromEraValue $ getEraValue txout

-- | Upgrade the internal representation of a 'TxOut'
-- to at least the 'Babbage' era.
--
-- Hardfork: Upgrade this function to a new era.
upgradeTxOutToBabbageOrLater :: TxOut -> TxOut
upgradeTxOutToBabbageOrLater x@(TxOutC (EraValue (txout :: Output era))) =
case theEra :: Era era of
Conway -> x
Babbage -> x
_ -> case upgradeToOutputBabbage txout of
Just output -> TxOutC (EraValue output)
_ -> error "upgradeTxOutToBabbageOrLater: impossible"

-- | Convert to an output in the 'Babbage' output, if possible.
--
-- Hardfork: Update this function to the current era.
toBabbageOutput :: TxOut -> Maybe (Output Babbage)
toBabbageOutput (TxOutC (EraValue txout)) = upgradeToOutputBabbage txout

-- | Convert to an output in the 'Conway' output
--
-- Hardfork: Update this function to the next era.
toConwayOutput :: TxOut -> Output Conway
toConwayOutput (TxOutC (EraValue txout)) = upgradeToOutputConway txout

{-----------------------------------------------------------------------------
Serialization
------------------------------------------------------------------------------}

-- | Serialize a 'TxOut' in binary format, e.g. for storing in a database.
serializeTxOut :: TxOut -> BL.ByteString
serializeTxOut (TxOutC (EraValue (txout :: Output era))) =
BL.cons tag (serializeOutput txout)
where
tag = toEnum (indexOfEra (theEra :: Era era))

type Dec era = Either DecoderError (Output era)

-- | Deserialize a 'TxOut' from the binary format.
--
-- prop> ∀ o. deserializeTxOut (serializeTxOut o) == Just o
deserializeTxOut :: BL.ByteString -> Either DecoderError TxOut
deserializeTxOut bytes
| Just (x,xs) <- BL.uncons bytes = do
eera <- maybe (Left $ errUnknownEraIndex x) Right
$ parseEraIndex (fromEnum x)
case eera of
EraValue (_ :: Era era) ->
TxOutC . EraValue <$> (deserializeOutput xs :: Dec era)
| otherwise =
Left $ DecoderErrorCustom "Empty input" ""
where
errUnknownEraIndex =
DecoderErrorCustom "Unknown era index" . T.pack . show

{-----------------------------------------------------------------------------
Transactions
------------------------------------------------------------------------------}

{-# INLINEABLE utxoFromEraTx #-}
-- | Unspent transaction outputs (UTxO) created by the transaction.
utxoFromEraTx :: forall era. IsEra era => Tx era -> Map.Map TxIn TxOut
utxoFromEraTx tx =
case Read.getScriptValidity tx of
Read.IsValid True -> utxoFromEraTxCollateralOutputs tx
Read.IsValid False -> utxoFromEraTxOutputs tx

{-# INLINEABLE utxoFromEraTxOutputs #-}
-- | UTxO corresponding to the ordinary outputs of a transaction.
--
-- This function ignores the transaction's script validity.
--
utxoFromEraTxOutputs
:: forall era. IsEra era => Tx era -> Map.Map TxIn TxOut
utxoFromEraTxOutputs tx =
withFoldableOutputs toMap (getEraOutputs tx)
where
txid = Read.getTxId tx
mkOutputInEra out = Output out :: Output era

toMap
:: forall t. Foldable t
=> t (OutputType era) -> Map.Map TxIn TxOut
toMap =
Map.fromList
. zipWith (\ix -> mkTxInTxOutPair txid ix . mkOutputInEra) [0..]
. toList

{-# INLINEABLE utxoFromEraTxCollateralOutputs #-}
-- | UTxO corresponding to the collateral outputs of a transaction.
--
-- This function ignores the transaction's script validity.
--
utxoFromEraTxCollateralOutputs
:: forall era. IsEra era => Tx era -> Map.Map TxIn TxOut
utxoFromEraTxCollateralOutputs tx =
withMaybeCollateralOutputs singleton (getEraCollateralOutputs tx)
where
txid = Read.getTxId tx
mkOutputInEra out = Output out :: Output era

singleton :: StrictMaybe (OutputType era) -> Map.Map TxIn TxOut
singleton =
Map.fromList
. map (mkTxInTxOutPair txid index . mkOutputInEra)
. toList

-- To reference a collateral output within transaction t, we specify an
-- output index that is equal to the number of ordinary outputs within t.
--
-- See definition of function "collOuts" within "Formal Specification of
-- the Cardano Ledger for the Babbage era".
--
-- https://github.com/IntersectMBO/cardano-ledger?tab=readme-ov-file
--
index :: Word16
index = fromIntegral $
withFoldableOutputs length (getEraOutputs tx)

-- Helper function: Create a pair @(TxIn, TxOut)@.
mkTxInTxOutPair
:: forall era. IsEra era
=> Read.TxId -> Word16 -> Output era -> (TxIn, TxOut)
mkTxInTxOutPair txid ix out =
( TxIn txid (TxIx ix)
, TxOutC (EraValue out)
)

-- Helper function: Treat the 'Outputs' as a 'Foldable' container.
withFoldableOutputs
:: forall era a. IsEra era
=> (forall t. Foldable t => t (OutputType era) -> a)
-> Outputs era
-> a
withFoldableOutputs f = case theEra :: Era era of
Byron -> \(Outputs x) -> f x
Shelley -> \(Outputs x) -> f x
Allegra -> \(Outputs x) -> f x
Mary -> \(Outputs x) -> f x
Alonzo -> \(Outputs x) -> f x
Babbage -> \(Outputs x) -> f x
Conway -> \(Outputs x) -> f x

-- Helper function: Treat the 'CollateralOutputs' as a 'StrictMaybe'.
withMaybeCollateralOutputs
:: forall era a. IsEra era
=> (StrictMaybe (OutputType era) -> a)
-> CollateralOutputs era
-> a
withMaybeCollateralOutputs f = case theEra :: Era era of
Byron -> \(CollateralOutputs _) -> f SNothing
Shelley -> \(CollateralOutputs _) -> f SNothing
Allegra -> \(CollateralOutputs _) -> f SNothing
Mary -> \(CollateralOutputs _) -> f SNothing
Alonzo -> \(CollateralOutputs _) -> f SNothing
Babbage -> \(CollateralOutputs x) -> f x
Conway -> \(CollateralOutputs x) -> f x
43 changes: 34 additions & 9 deletions lib/read/lib/Cardano/Wallet/Read/Value.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}

{- |
Expand Down Expand Up @@ -29,7 +31,7 @@ module Cardano.Wallet.Read.Value
, lessOrEqual

-- * Internal
, fromMaryValue
, fromEraValue
, toMaryValue
) where

Expand All @@ -47,10 +49,15 @@ import Cardano.Ledger.Val
( pointwise
, (<->)
)
import Cardano.Read.Ledger.Eras
( Era (..)
, IsEra (..)
)

import qualified Cardano.Ledger.BaseTypes as SH
import qualified Cardano.Ledger.Coin as L
import qualified Cardano.Ledger.Mary.Value as MA
import qualified Cardano.Read.Ledger.Value as L

{-----------------------------------------------------------------------------
Coin
Expand Down Expand Up @@ -85,14 +92,6 @@ type MultiAsset = MA.MultiAsset StandardCrypto
-- | Monetary values, representing both ADA and native assets/tokens.
newtype Value = Value (MA.MaryValue StandardCrypto)

-- | Internal: Convert from ledger 'MaryValue'.
fromMaryValue :: MA.MaryValue StandardCrypto -> Value
fromMaryValue = Value

-- | Internal: Convert to ledger 'MaryValue'.
toMaryValue :: Value -> MA.MaryValue StandardCrypto
toMaryValue (Value v) = v

instance Eq Value where
(Value x) == (Value y) = x == y

Expand Down Expand Up @@ -145,3 +144,29 @@ subtract (Value x) (Value y) = Value (x <-> y)
lessOrEqual :: Value -> Value -> Bool
lessOrEqual (Value value1) (Value value2) =
pointwise (<=) value1 value2

{-----------------------------------------------------------------------------
Conversions from Eras
------------------------------------------------------------------------------}
-- | Internal: Convert from ledger 'MaryValue'.
fromMaryValue :: MA.MaryValue StandardCrypto -> Value
fromMaryValue = Value

-- | Internal: Convert to ledger 'MaryValue'.
toMaryValue :: Value -> MA.MaryValue StandardCrypto
toMaryValue (Value v) = v

-- | Internal: Convert from era-indexed 'L.Value'.
fromEraValue :: forall era. IsEra era => L.Value era -> Value
fromEraValue = fromMaryValue . case theEra :: Era era of
Byron -> onValue L.maryValueFromByronValue
Shelley -> onValue L.maryValueFromShelleyValue
Allegra -> onValue L.maryValueFromShelleyValue
Mary -> onValue id
Alonzo -> onValue id
Babbage -> onValue id
Conway -> onValue id

-- Helper function for type inference.
onValue :: (L.ValueType era -> t) -> L.Value era -> t
onValue f (L.Value x) = f x
Loading

0 comments on commit 933b15f

Please sign in to comment.