Skip to content

Commit

Permalink
wip Add Cardano.Wallet.Read.Tx.TxOut
Browse files Browse the repository at this point in the history
  • Loading branch information
HeinrichApfelmus committed Jul 26, 2024
1 parent 0cf77ab commit 1deb893
Show file tree
Hide file tree
Showing 3 changed files with 173 additions and 0 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 @@ -98,6 +98,8 @@ library
Cardano.Wallet.Read.Tx.Inputs
Cardano.Wallet.Read.Tx.TxId
Cardano.Wallet.Read.Tx.TxIn
Cardano.Wallet.Read.Tx.TxOut
Cardano.Wallet.Read.Value

build-depends:
, base
Expand Down
98 changes: 98 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,98 @@
{-# LANGUAGE ScopedTypeVariables #-}

-- |
-- Copyright: © 2024 Cardano Foundation
-- License: Apache-2.0
--
-- 'TxOut' — transaction output.
--

module Cardano.Wallet.Read.Tx.TxOut
( TxOut
, pattern TxOut
)
where

import Prelude

import Cardano.Ledger.Api.Tx.Out
( valueTxOutL
)
import Cardano.Ledger.Crypto
( StandardCrypto
)
import Cardano.Read.Ledger.Tx.Outputs
( Output (..)
)
import Cardano.Wallet.Read.Eras
( Allegra
, Alonzo
, Babbage
, Byron
, Conway
, Era (..)
, EraValue (..)
, Mary
, Shelley
)
import Cardano.Wallet.Read.Tx.TxIn
( TxIx
)
import Control.Lens
( (^.)
)

import qualified Cardano.Wallet.Read.Value as Value
import qualified Data.Map.Strict as Map

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

{-
-- | We use a compact representation of addresses.
type Address = CompactAddress StandardCrypto
getAddress :: TxOut -> Address
getAddress = undefined
-}

getValue :: TxOut -> Value
getValue (TxOutC (EraValue (txout :: Output era))) =
case theEra :: Era era of
Byron -> fromByronValue (BY.txOutValue txout)
Shelley -> fromShelleyValue (txout ^. valueTxOutL)
Allegra -> fromMaryValue (txout ^. valueTxOutL)
Mary -> fromMaryValue (txout ^. valueTxOutL)
Alonzo -> fromMaryValue (txout ^. valueTxOutL)
Babbage -> fromMaryValue (txout ^. valueTxOutL)
Conway -> fromMaryValue (txout ^. valueTxOutL)

fromByronValue :: BY.Lovelace -> Value
fromByronValue = undefined

fromShelleyValue :: SH.ShelleyValue -> Value
fromShelleyValue = undefined

fromMaryValue :: SH.MaryValue era -> Value
fromMaryValue (SH.MaryValue coin multiasset) = undefined

{-----------------------------------------------------------------------------
Functions
------------------------------------------------------------------------------}

{-# INLINEABLE getOutputs #-}
getOutputs :: forall era. IsEra era => Tx era -> Map.Map TxIx TxOut
getOutputs = case theEra :: Era era of
Byron -> onTx $ Outputs . BY.txOutputs . BY.taTx
Shelley -> outputs
Allegra -> outputs
Mary -> outputs
Alonzo -> outputs
Babbage -> outputs
Conway -> outputs
where
outputs = onTx $ Outputs . view (bodyTxL . outputsTxBodyL)
73 changes: 73 additions & 0 deletions lib/read/lib/Cardano/Wallet/Read/Value.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,73 @@
--
-- NOTE: This file will be generated by agda2hs.
--
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE StandaloneDeriving #-}

{- |
Copyright: © 2024 Cardano Foundation
License: Apache-2.0
'Value' — ADA and tokens.
-}
module Cardano.Wallet.Read.Value where

import Prelude

import qualified Data.ByteString as BS (ByteString)
import qualified Data.Map.Strict as Map
( Map
, empty
, fromList
)
import Numeric.Natural (Natural)

type Coin = Natural

monusCoin :: Coin -> Coin -> Coin
monusCoin a b =
case a < b of
False -> a - b
True -> 0

type AssetName = BS.ByteString

type ScriptHash = BS.ByteString

type PolicyID = ScriptHash

type Quantity = Integer

data AssetID
= AdaID
| Asset PolicyID AssetName

deriving instance Eq AssetID

deriving instance Ord AssetID

data Value = Value
{ ada :: Coin
, assets :: Map.Map (PolicyID, AssetName) Quantity
}

deriving instance Eq Value

valueFromList :: Coin -> [(PolicyID, AssetName, Quantity)] -> Value
valueFromList coin xs =
Value
coin
( Map.fromList
( map
( \case
(p, n, q) -> ((p, n), q)
)
xs
)
)

injectCoin :: Coin -> Value
injectCoin coin = Value coin Map.empty

getCoin :: Value -> Coin
getCoin v = ada v

0 comments on commit 1deb893

Please sign in to comment.