{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Ledger.Tx.Internal
( module Ledger.Tx.Internal
, Language(..)
, TxOut (..)
, TxOutRef (..)
, Versioned(..)
) where
import Cardano.Api qualified as C
import Cardano.Api.Shelley qualified as C hiding (toShelleyTxOut)
import Cardano.Binary qualified as C
import Cardano.Ledger.Alonzo.Genesis ()
import Codec.CBOR.Write qualified as Write
import Codec.Serialise (Serialise, decode, encode)
import Control.Applicative (empty, (<|>))
import Control.DeepSeq (NFData, rnf)
import Control.Lens ((&), (.~), (?~))
import Cardano.Ledger.Core qualified as Ledger (TxOut)
import Cardano.Ledger.Serialization qualified as Ledger (Sized, mkSized)
import Ouroboros.Consensus.Shelley.Eras qualified as Ledger
import Control.Lens qualified as L
import Control.Monad.State.Strict (execState, modify')
import Data.Aeson (FromJSON, ToJSON)
import Data.ByteArray qualified as BA
import Data.Data (Proxy (Proxy))
import Data.Foldable (traverse_)
import Data.Map (Map)
import Data.Map qualified as Map
import Data.OpenApi qualified as OpenApi
import GHC.Generics (Generic)
import Ledger.Address (CardanoAddress, cardanoPubKeyHash, toPlutusAddress)
import Ledger.Contexts.Orphans ()
import Ledger.Crypto
import Ledger.DCert.Orphans ()
import Ledger.Slot
import Ledger.Tx.CardanoAPI.Internal (fromCardanoTxOutDatum, fromCardanoTxOutValue, fromCardanoValue)
import Ledger.Tx.CardanoAPITemp qualified as C
import Ledger.Tx.Orphans ()
import Ledger.Tx.Orphans.V2 ()
import Plutus.Script.Utils.Scripts
import Plutus.V1.Ledger.Api (Credential, DCert, ScriptPurpose (..), StakingCredential (StakingHash), dataToBuiltinData)
import Plutus.V1.Ledger.Scripts
import Plutus.V1.Ledger.Tx hiding (TxIn (..), TxInType (..), TxOut (..), inRef, inScripts, inType, pubKeyTxIn,
pubKeyTxIns, scriptTxIn, scriptTxIns)
import Plutus.V1.Ledger.Value as V
import Plutus.V2.Ledger.Api qualified as PV2
import PlutusTx.Lattice
import PlutusTx.Prelude (BuiltinByteString)
import PlutusTx.Prelude qualified as PlutusTx
import Prettyprinter (Pretty (..), hang, viaShow, vsep, (<+>))
data TxInType =
ScriptAddress !(Either (Versioned Validator) (Versioned TxOutRef)) !Redeemer !(Maybe Datum)
| ConsumePublicKeyAddress
| ConsumeSimpleScriptAddress
deriving stock (Int -> TxInType -> ShowS
[TxInType] -> ShowS
TxInType -> String
(Int -> TxInType -> ShowS)
-> (TxInType -> String) -> ([TxInType] -> ShowS) -> Show TxInType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxInType] -> ShowS
$cshowList :: [TxInType] -> ShowS
show :: TxInType -> String
$cshow :: TxInType -> String
showsPrec :: Int -> TxInType -> ShowS
$cshowsPrec :: Int -> TxInType -> ShowS
Show, TxInType -> TxInType -> Bool
(TxInType -> TxInType -> Bool)
-> (TxInType -> TxInType -> Bool) -> Eq TxInType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxInType -> TxInType -> Bool
$c/= :: TxInType -> TxInType -> Bool
== :: TxInType -> TxInType -> Bool
$c== :: TxInType -> TxInType -> Bool
Eq, Eq TxInType
Eq TxInType
-> (TxInType -> TxInType -> Ordering)
-> (TxInType -> TxInType -> Bool)
-> (TxInType -> TxInType -> Bool)
-> (TxInType -> TxInType -> Bool)
-> (TxInType -> TxInType -> Bool)
-> (TxInType -> TxInType -> TxInType)
-> (TxInType -> TxInType -> TxInType)
-> Ord TxInType
TxInType -> TxInType -> Bool
TxInType -> TxInType -> Ordering
TxInType -> TxInType -> TxInType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TxInType -> TxInType -> TxInType
$cmin :: TxInType -> TxInType -> TxInType
max :: TxInType -> TxInType -> TxInType
$cmax :: TxInType -> TxInType -> TxInType
>= :: TxInType -> TxInType -> Bool
$c>= :: TxInType -> TxInType -> Bool
> :: TxInType -> TxInType -> Bool
$c> :: TxInType -> TxInType -> Bool
<= :: TxInType -> TxInType -> Bool
$c<= :: TxInType -> TxInType -> Bool
< :: TxInType -> TxInType -> Bool
$c< :: TxInType -> TxInType -> Bool
compare :: TxInType -> TxInType -> Ordering
$ccompare :: TxInType -> TxInType -> Ordering
$cp1Ord :: Eq TxInType
Ord, (forall x. TxInType -> Rep TxInType x)
-> (forall x. Rep TxInType x -> TxInType) -> Generic TxInType
forall x. Rep TxInType x -> TxInType
forall x. TxInType -> Rep TxInType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxInType x -> TxInType
$cfrom :: forall x. TxInType -> Rep TxInType x
Generic)
deriving anyclass ([TxInType] -> Encoding
[TxInType] -> Value
TxInType -> Encoding
TxInType -> Value
(TxInType -> Value)
-> (TxInType -> Encoding)
-> ([TxInType] -> Value)
-> ([TxInType] -> Encoding)
-> ToJSON TxInType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TxInType] -> Encoding
$ctoEncodingList :: [TxInType] -> Encoding
toJSONList :: [TxInType] -> Value
$ctoJSONList :: [TxInType] -> Value
toEncoding :: TxInType -> Encoding
$ctoEncoding :: TxInType -> Encoding
toJSON :: TxInType -> Value
$ctoJSON :: TxInType -> Value
ToJSON, Value -> Parser [TxInType]
Value -> Parser TxInType
(Value -> Parser TxInType)
-> (Value -> Parser [TxInType]) -> FromJSON TxInType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TxInType]
$cparseJSONList :: Value -> Parser [TxInType]
parseJSON :: Value -> Parser TxInType
$cparseJSON :: Value -> Parser TxInType
FromJSON, [TxInType] -> Encoding
TxInType -> Encoding
(TxInType -> Encoding)
-> (forall s. Decoder s TxInType)
-> ([TxInType] -> Encoding)
-> (forall s. Decoder s [TxInType])
-> Serialise TxInType
forall s. Decoder s [TxInType]
forall s. Decoder s TxInType
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
decodeList :: Decoder s [TxInType]
$cdecodeList :: forall s. Decoder s [TxInType]
encodeList :: [TxInType] -> Encoding
$cencodeList :: [TxInType] -> Encoding
decode :: Decoder s TxInType
$cdecode :: forall s. Decoder s TxInType
encode :: TxInType -> Encoding
$cencode :: TxInType -> Encoding
Serialise, TxInType -> ()
(TxInType -> ()) -> NFData TxInType
forall a. (a -> ()) -> NFData a
rnf :: TxInType -> ()
$crnf :: TxInType -> ()
NFData, Typeable TxInType
Typeable TxInType
-> (Proxy TxInType -> Declare (Definitions Schema) NamedSchema)
-> ToSchema TxInType
Proxy TxInType -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a
-> (Proxy a -> Declare (Definitions Schema) NamedSchema)
-> ToSchema a
declareNamedSchema :: Proxy TxInType -> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy TxInType -> Declare (Definitions Schema) NamedSchema
$cp1ToSchema :: Typeable TxInType
OpenApi.ToSchema)
data TxIn = TxIn {
TxIn -> TxOutRef
txInRef :: !TxOutRef,
TxIn -> Maybe TxInType
txInType :: Maybe TxInType
}
deriving stock (Int -> TxIn -> ShowS
[TxIn] -> ShowS
TxIn -> String
(Int -> TxIn -> ShowS)
-> (TxIn -> String) -> ([TxIn] -> ShowS) -> Show TxIn
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxIn] -> ShowS
$cshowList :: [TxIn] -> ShowS
show :: TxIn -> String
$cshow :: TxIn -> String
showsPrec :: Int -> TxIn -> ShowS
$cshowsPrec :: Int -> TxIn -> ShowS
Show, TxIn -> TxIn -> Bool
(TxIn -> TxIn -> Bool) -> (TxIn -> TxIn -> Bool) -> Eq TxIn
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxIn -> TxIn -> Bool
$c/= :: TxIn -> TxIn -> Bool
== :: TxIn -> TxIn -> Bool
$c== :: TxIn -> TxIn -> Bool
Eq, Eq TxIn
Eq TxIn
-> (TxIn -> TxIn -> Ordering)
-> (TxIn -> TxIn -> Bool)
-> (TxIn -> TxIn -> Bool)
-> (TxIn -> TxIn -> Bool)
-> (TxIn -> TxIn -> Bool)
-> (TxIn -> TxIn -> TxIn)
-> (TxIn -> TxIn -> TxIn)
-> Ord TxIn
TxIn -> TxIn -> Bool
TxIn -> TxIn -> Ordering
TxIn -> TxIn -> TxIn
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TxIn -> TxIn -> TxIn
$cmin :: TxIn -> TxIn -> TxIn
max :: TxIn -> TxIn -> TxIn
$cmax :: TxIn -> TxIn -> TxIn
>= :: TxIn -> TxIn -> Bool
$c>= :: TxIn -> TxIn -> Bool
> :: TxIn -> TxIn -> Bool
$c> :: TxIn -> TxIn -> Bool
<= :: TxIn -> TxIn -> Bool
$c<= :: TxIn -> TxIn -> Bool
< :: TxIn -> TxIn -> Bool
$c< :: TxIn -> TxIn -> Bool
compare :: TxIn -> TxIn -> Ordering
$ccompare :: TxIn -> TxIn -> Ordering
$cp1Ord :: Eq TxIn
Ord, (forall x. TxIn -> Rep TxIn x)
-> (forall x. Rep TxIn x -> TxIn) -> Generic TxIn
forall x. Rep TxIn x -> TxIn
forall x. TxIn -> Rep TxIn x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxIn x -> TxIn
$cfrom :: forall x. TxIn -> Rep TxIn x
Generic)
deriving anyclass ([TxIn] -> Encoding
[TxIn] -> Value
TxIn -> Encoding
TxIn -> Value
(TxIn -> Value)
-> (TxIn -> Encoding)
-> ([TxIn] -> Value)
-> ([TxIn] -> Encoding)
-> ToJSON TxIn
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TxIn] -> Encoding
$ctoEncodingList :: [TxIn] -> Encoding
toJSONList :: [TxIn] -> Value
$ctoJSONList :: [TxIn] -> Value
toEncoding :: TxIn -> Encoding
$ctoEncoding :: TxIn -> Encoding
toJSON :: TxIn -> Value
$ctoJSON :: TxIn -> Value
ToJSON, Value -> Parser [TxIn]
Value -> Parser TxIn
(Value -> Parser TxIn) -> (Value -> Parser [TxIn]) -> FromJSON TxIn
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TxIn]
$cparseJSONList :: Value -> Parser [TxIn]
parseJSON :: Value -> Parser TxIn
$cparseJSON :: Value -> Parser TxIn
FromJSON, [TxIn] -> Encoding
TxIn -> Encoding
(TxIn -> Encoding)
-> (forall s. Decoder s TxIn)
-> ([TxIn] -> Encoding)
-> (forall s. Decoder s [TxIn])
-> Serialise TxIn
forall s. Decoder s [TxIn]
forall s. Decoder s TxIn
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
decodeList :: Decoder s [TxIn]
$cdecodeList :: forall s. Decoder s [TxIn]
encodeList :: [TxIn] -> Encoding
$cencodeList :: [TxIn] -> Encoding
decode :: Decoder s TxIn
$cdecode :: forall s. Decoder s TxIn
encode :: TxIn -> Encoding
$cencode :: TxIn -> Encoding
Serialise, TxIn -> ()
(TxIn -> ()) -> NFData TxIn
forall a. (a -> ()) -> NFData a
rnf :: TxIn -> ()
$crnf :: TxIn -> ()
NFData, Typeable TxIn
Typeable TxIn
-> (Proxy TxIn -> Declare (Definitions Schema) NamedSchema)
-> ToSchema TxIn
Proxy TxIn -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a
-> (Proxy a -> Declare (Definitions Schema) NamedSchema)
-> ToSchema a
declareNamedSchema :: Proxy TxIn -> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy TxIn -> Declare (Definitions Schema) NamedSchema
$cp1ToSchema :: Typeable TxIn
OpenApi.ToSchema)
instance Pretty TxIn where
pretty :: TxIn -> Doc ann
pretty TxIn{TxOutRef
txInRef :: TxOutRef
txInRef :: TxIn -> TxOutRef
txInRef,Maybe TxInType
txInType :: Maybe TxInType
txInType :: TxIn -> Maybe TxInType
txInType} =
let rest :: Doc ann
rest =
case Maybe TxInType
txInType of
Just (ScriptAddress Either (Versioned Validator) (Versioned TxOutRef)
_ Redeemer
redeemer Maybe Datum
_) ->
Redeemer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Redeemer
redeemer
Maybe TxInType
_ -> Doc ann
forall a. Monoid a => a
mempty
in Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"-" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxOutRef -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOutRef
txInRef, Item [Doc ann]
Doc ann
rest]
pubKeyTxIn :: TxOutRef -> TxIn
pubKeyTxIn :: TxOutRef -> TxIn
pubKeyTxIn TxOutRef
r = TxOutRef -> Maybe TxInType -> TxIn
TxIn TxOutRef
r (TxInType -> Maybe TxInType
forall a. a -> Maybe a
Just TxInType
ConsumePublicKeyAddress)
scriptTxIn :: TxOutRef -> Versioned Validator -> Redeemer -> Maybe Datum -> TxIn
scriptTxIn :: TxOutRef -> Versioned Validator -> Redeemer -> Maybe Datum -> TxIn
scriptTxIn TxOutRef
ref Versioned Validator
v Redeemer
r Maybe Datum
d = TxOutRef -> Maybe TxInType -> TxIn
TxIn TxOutRef
ref (Maybe TxInType -> TxIn)
-> (TxInType -> Maybe TxInType) -> TxInType -> TxIn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxInType -> Maybe TxInType
forall a. a -> Maybe a
Just (TxInType -> TxIn) -> TxInType -> TxIn
forall a b. (a -> b) -> a -> b
$ Either (Versioned Validator) (Versioned TxOutRef)
-> Redeemer -> Maybe Datum -> TxInType
ScriptAddress (Versioned Validator
-> Either (Versioned Validator) (Versioned TxOutRef)
forall a b. a -> Either a b
Left Versioned Validator
v) Redeemer
r Maybe Datum
d
data TxInputType =
TxScriptAddress !Redeemer !(Either ValidatorHash (Versioned TxOutRef)) !(Maybe DatumHash)
| TxConsumePublicKeyAddress
| TxConsumeSimpleScriptAddress
deriving stock (Int -> TxInputType -> ShowS
[TxInputType] -> ShowS
TxInputType -> String
(Int -> TxInputType -> ShowS)
-> (TxInputType -> String)
-> ([TxInputType] -> ShowS)
-> Show TxInputType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxInputType] -> ShowS
$cshowList :: [TxInputType] -> ShowS
show :: TxInputType -> String
$cshow :: TxInputType -> String
showsPrec :: Int -> TxInputType -> ShowS
$cshowsPrec :: Int -> TxInputType -> ShowS
Show, TxInputType -> TxInputType -> Bool
(TxInputType -> TxInputType -> Bool)
-> (TxInputType -> TxInputType -> Bool) -> Eq TxInputType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxInputType -> TxInputType -> Bool
$c/= :: TxInputType -> TxInputType -> Bool
== :: TxInputType -> TxInputType -> Bool
$c== :: TxInputType -> TxInputType -> Bool
Eq, Eq TxInputType
Eq TxInputType
-> (TxInputType -> TxInputType -> Ordering)
-> (TxInputType -> TxInputType -> Bool)
-> (TxInputType -> TxInputType -> Bool)
-> (TxInputType -> TxInputType -> Bool)
-> (TxInputType -> TxInputType -> Bool)
-> (TxInputType -> TxInputType -> TxInputType)
-> (TxInputType -> TxInputType -> TxInputType)
-> Ord TxInputType
TxInputType -> TxInputType -> Bool
TxInputType -> TxInputType -> Ordering
TxInputType -> TxInputType -> TxInputType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TxInputType -> TxInputType -> TxInputType
$cmin :: TxInputType -> TxInputType -> TxInputType
max :: TxInputType -> TxInputType -> TxInputType
$cmax :: TxInputType -> TxInputType -> TxInputType
>= :: TxInputType -> TxInputType -> Bool
$c>= :: TxInputType -> TxInputType -> Bool
> :: TxInputType -> TxInputType -> Bool
$c> :: TxInputType -> TxInputType -> Bool
<= :: TxInputType -> TxInputType -> Bool
$c<= :: TxInputType -> TxInputType -> Bool
< :: TxInputType -> TxInputType -> Bool
$c< :: TxInputType -> TxInputType -> Bool
compare :: TxInputType -> TxInputType -> Ordering
$ccompare :: TxInputType -> TxInputType -> Ordering
$cp1Ord :: Eq TxInputType
Ord, (forall x. TxInputType -> Rep TxInputType x)
-> (forall x. Rep TxInputType x -> TxInputType)
-> Generic TxInputType
forall x. Rep TxInputType x -> TxInputType
forall x. TxInputType -> Rep TxInputType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxInputType x -> TxInputType
$cfrom :: forall x. TxInputType -> Rep TxInputType x
Generic)
deriving anyclass ([TxInputType] -> Encoding
[TxInputType] -> Value
TxInputType -> Encoding
TxInputType -> Value
(TxInputType -> Value)
-> (TxInputType -> Encoding)
-> ([TxInputType] -> Value)
-> ([TxInputType] -> Encoding)
-> ToJSON TxInputType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TxInputType] -> Encoding
$ctoEncodingList :: [TxInputType] -> Encoding
toJSONList :: [TxInputType] -> Value
$ctoJSONList :: [TxInputType] -> Value
toEncoding :: TxInputType -> Encoding
$ctoEncoding :: TxInputType -> Encoding
toJSON :: TxInputType -> Value
$ctoJSON :: TxInputType -> Value
ToJSON, Value -> Parser [TxInputType]
Value -> Parser TxInputType
(Value -> Parser TxInputType)
-> (Value -> Parser [TxInputType]) -> FromJSON TxInputType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TxInputType]
$cparseJSONList :: Value -> Parser [TxInputType]
parseJSON :: Value -> Parser TxInputType
$cparseJSON :: Value -> Parser TxInputType
FromJSON, [TxInputType] -> Encoding
TxInputType -> Encoding
(TxInputType -> Encoding)
-> (forall s. Decoder s TxInputType)
-> ([TxInputType] -> Encoding)
-> (forall s. Decoder s [TxInputType])
-> Serialise TxInputType
forall s. Decoder s [TxInputType]
forall s. Decoder s TxInputType
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
decodeList :: Decoder s [TxInputType]
$cdecodeList :: forall s. Decoder s [TxInputType]
encodeList :: [TxInputType] -> Encoding
$cencodeList :: [TxInputType] -> Encoding
decode :: Decoder s TxInputType
$cdecode :: forall s. Decoder s TxInputType
encode :: TxInputType -> Encoding
$cencode :: TxInputType -> Encoding
Serialise, TxInputType -> ()
(TxInputType -> ()) -> NFData TxInputType
forall a. (a -> ()) -> NFData a
rnf :: TxInputType -> ()
$crnf :: TxInputType -> ()
NFData)
data TxInput = TxInput {
TxInput -> TxOutRef
txInputRef :: !TxOutRef,
TxInput -> TxInputType
txInputType :: !TxInputType
}
deriving stock (Int -> TxInput -> ShowS
[TxInput] -> ShowS
TxInput -> String
(Int -> TxInput -> ShowS)
-> (TxInput -> String) -> ([TxInput] -> ShowS) -> Show TxInput
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxInput] -> ShowS
$cshowList :: [TxInput] -> ShowS
show :: TxInput -> String
$cshow :: TxInput -> String
showsPrec :: Int -> TxInput -> ShowS
$cshowsPrec :: Int -> TxInput -> ShowS
Show, TxInput -> TxInput -> Bool
(TxInput -> TxInput -> Bool)
-> (TxInput -> TxInput -> Bool) -> Eq TxInput
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxInput -> TxInput -> Bool
$c/= :: TxInput -> TxInput -> Bool
== :: TxInput -> TxInput -> Bool
$c== :: TxInput -> TxInput -> Bool
Eq, Eq TxInput
Eq TxInput
-> (TxInput -> TxInput -> Ordering)
-> (TxInput -> TxInput -> Bool)
-> (TxInput -> TxInput -> Bool)
-> (TxInput -> TxInput -> Bool)
-> (TxInput -> TxInput -> Bool)
-> (TxInput -> TxInput -> TxInput)
-> (TxInput -> TxInput -> TxInput)
-> Ord TxInput
TxInput -> TxInput -> Bool
TxInput -> TxInput -> Ordering
TxInput -> TxInput -> TxInput
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TxInput -> TxInput -> TxInput
$cmin :: TxInput -> TxInput -> TxInput
max :: TxInput -> TxInput -> TxInput
$cmax :: TxInput -> TxInput -> TxInput
>= :: TxInput -> TxInput -> Bool
$c>= :: TxInput -> TxInput -> Bool
> :: TxInput -> TxInput -> Bool
$c> :: TxInput -> TxInput -> Bool
<= :: TxInput -> TxInput -> Bool
$c<= :: TxInput -> TxInput -> Bool
< :: TxInput -> TxInput -> Bool
$c< :: TxInput -> TxInput -> Bool
compare :: TxInput -> TxInput -> Ordering
$ccompare :: TxInput -> TxInput -> Ordering
$cp1Ord :: Eq TxInput
Ord, (forall x. TxInput -> Rep TxInput x)
-> (forall x. Rep TxInput x -> TxInput) -> Generic TxInput
forall x. Rep TxInput x -> TxInput
forall x. TxInput -> Rep TxInput x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxInput x -> TxInput
$cfrom :: forall x. TxInput -> Rep TxInput x
Generic)
deriving anyclass ([TxInput] -> Encoding
[TxInput] -> Value
TxInput -> Encoding
TxInput -> Value
(TxInput -> Value)
-> (TxInput -> Encoding)
-> ([TxInput] -> Value)
-> ([TxInput] -> Encoding)
-> ToJSON TxInput
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TxInput] -> Encoding
$ctoEncodingList :: [TxInput] -> Encoding
toJSONList :: [TxInput] -> Value
$ctoJSONList :: [TxInput] -> Value
toEncoding :: TxInput -> Encoding
$ctoEncoding :: TxInput -> Encoding
toJSON :: TxInput -> Value
$ctoJSON :: TxInput -> Value
ToJSON, Value -> Parser [TxInput]
Value -> Parser TxInput
(Value -> Parser TxInput)
-> (Value -> Parser [TxInput]) -> FromJSON TxInput
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TxInput]
$cparseJSONList :: Value -> Parser [TxInput]
parseJSON :: Value -> Parser TxInput
$cparseJSON :: Value -> Parser TxInput
FromJSON, [TxInput] -> Encoding
TxInput -> Encoding
(TxInput -> Encoding)
-> (forall s. Decoder s TxInput)
-> ([TxInput] -> Encoding)
-> (forall s. Decoder s [TxInput])
-> Serialise TxInput
forall s. Decoder s [TxInput]
forall s. Decoder s TxInput
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
decodeList :: Decoder s [TxInput]
$cdecodeList :: forall s. Decoder s [TxInput]
encodeList :: [TxInput] -> Encoding
$cencodeList :: [TxInput] -> Encoding
decode :: Decoder s TxInput
$cdecode :: forall s. Decoder s TxInput
encode :: TxInput -> Encoding
$cencode :: TxInput -> Encoding
Serialise, TxInput -> ()
(TxInput -> ()) -> NFData TxInput
forall a. (a -> ()) -> NFData a
rnf :: TxInput -> ()
$crnf :: TxInput -> ()
NFData)
instance Pretty TxInput where
pretty :: TxInput -> Doc ann
pretty TxInput{TxOutRef
txInputRef :: TxOutRef
txInputRef :: TxInput -> TxOutRef
txInputRef,TxInputType
txInputType :: TxInputType
txInputType :: TxInput -> TxInputType
txInputType} =
let rest :: Doc ann
rest =
case TxInputType
txInputType of
TxScriptAddress Redeemer
redeemer Either ValidatorHash (Versioned TxOutRef)
_ Maybe DatumHash
_ ->
Redeemer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Redeemer
redeemer
TxInputType
_ -> Doc ann
forall a. Monoid a => a
mempty
in Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"-" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxOutRef -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOutRef
txInputRef, Item [Doc ann]
Doc ann
rest]
inputRef :: L.Lens' TxInput TxOutRef
inputRef :: (TxOutRef -> f TxOutRef) -> TxInput -> f TxInput
inputRef = (TxInput -> TxOutRef)
-> (TxInput -> TxOutRef -> TxInput)
-> Lens TxInput TxInput TxOutRef TxOutRef
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens TxInput -> TxOutRef
txInputRef TxInput -> TxOutRef -> TxInput
s where
s :: TxInput -> TxOutRef -> TxInput
s TxInput
txi TxOutRef
r = TxInput
txi { txInputRef :: TxOutRef
txInputRef = TxOutRef
r }
inputType :: L.Lens' TxInput TxInputType
inputType :: (TxInputType -> f TxInputType) -> TxInput -> f TxInput
inputType = (TxInput -> TxInputType)
-> (TxInput -> TxInputType -> TxInput)
-> Lens TxInput TxInput TxInputType TxInputType
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens TxInput -> TxInputType
txInputType TxInput -> TxInputType -> TxInput
s where
s :: TxInput -> TxInputType -> TxInput
s TxInput
txi TxInputType
t = TxInput
txi { txInputType :: TxInputType
txInputType = TxInputType
t }
data Withdrawal = Withdrawal
{ Withdrawal -> Credential
withdrawalCredential :: Credential
, Withdrawal -> Integer
withdrawalAmount :: Integer
, Withdrawal -> Maybe Redeemer
withdrawalRedeemer :: Maybe Redeemer
}
deriving stock (Int -> Withdrawal -> ShowS
[Withdrawal] -> ShowS
Withdrawal -> String
(Int -> Withdrawal -> ShowS)
-> (Withdrawal -> String)
-> ([Withdrawal] -> ShowS)
-> Show Withdrawal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Withdrawal] -> ShowS
$cshowList :: [Withdrawal] -> ShowS
show :: Withdrawal -> String
$cshow :: Withdrawal -> String
showsPrec :: Int -> Withdrawal -> ShowS
$cshowsPrec :: Int -> Withdrawal -> ShowS
Show, Withdrawal -> Withdrawal -> Bool
(Withdrawal -> Withdrawal -> Bool)
-> (Withdrawal -> Withdrawal -> Bool) -> Eq Withdrawal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Withdrawal -> Withdrawal -> Bool
$c/= :: Withdrawal -> Withdrawal -> Bool
== :: Withdrawal -> Withdrawal -> Bool
$c== :: Withdrawal -> Withdrawal -> Bool
Eq, (forall x. Withdrawal -> Rep Withdrawal x)
-> (forall x. Rep Withdrawal x -> Withdrawal) -> Generic Withdrawal
forall x. Rep Withdrawal x -> Withdrawal
forall x. Withdrawal -> Rep Withdrawal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Withdrawal x -> Withdrawal
$cfrom :: forall x. Withdrawal -> Rep Withdrawal x
Generic)
deriving anyclass ([Withdrawal] -> Encoding
[Withdrawal] -> Value
Withdrawal -> Encoding
Withdrawal -> Value
(Withdrawal -> Value)
-> (Withdrawal -> Encoding)
-> ([Withdrawal] -> Value)
-> ([Withdrawal] -> Encoding)
-> ToJSON Withdrawal
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Withdrawal] -> Encoding
$ctoEncodingList :: [Withdrawal] -> Encoding
toJSONList :: [Withdrawal] -> Value
$ctoJSONList :: [Withdrawal] -> Value
toEncoding :: Withdrawal -> Encoding
$ctoEncoding :: Withdrawal -> Encoding
toJSON :: Withdrawal -> Value
$ctoJSON :: Withdrawal -> Value
ToJSON, Value -> Parser [Withdrawal]
Value -> Parser Withdrawal
(Value -> Parser Withdrawal)
-> (Value -> Parser [Withdrawal]) -> FromJSON Withdrawal
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Withdrawal]
$cparseJSONList :: Value -> Parser [Withdrawal]
parseJSON :: Value -> Parser Withdrawal
$cparseJSON :: Value -> Parser Withdrawal
FromJSON, [Withdrawal] -> Encoding
Withdrawal -> Encoding
(Withdrawal -> Encoding)
-> (forall s. Decoder s Withdrawal)
-> ([Withdrawal] -> Encoding)
-> (forall s. Decoder s [Withdrawal])
-> Serialise Withdrawal
forall s. Decoder s [Withdrawal]
forall s. Decoder s Withdrawal
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
decodeList :: Decoder s [Withdrawal]
$cdecodeList :: forall s. Decoder s [Withdrawal]
encodeList :: [Withdrawal] -> Encoding
$cencodeList :: [Withdrawal] -> Encoding
decode :: Decoder s Withdrawal
$cdecode :: forall s. Decoder s Withdrawal
encode :: Withdrawal -> Encoding
$cencode :: Withdrawal -> Encoding
Serialise, Withdrawal -> ()
(Withdrawal -> ()) -> NFData Withdrawal
forall a. (a -> ()) -> NFData a
rnf :: Withdrawal -> ()
$crnf :: Withdrawal -> ()
NFData)
instance Pretty Withdrawal where
pretty :: Withdrawal -> Doc ann
pretty = Withdrawal -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow
data Certificate = Certificate
{ Certificate -> DCert
certificateDcert :: DCert
, Certificate -> Maybe Redeemer
certificateRedeemer :: Maybe Redeemer
}
deriving stock (Int -> Certificate -> ShowS
[Certificate] -> ShowS
Certificate -> String
(Int -> Certificate -> ShowS)
-> (Certificate -> String)
-> ([Certificate] -> ShowS)
-> Show Certificate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Certificate] -> ShowS
$cshowList :: [Certificate] -> ShowS
show :: Certificate -> String
$cshow :: Certificate -> String
showsPrec :: Int -> Certificate -> ShowS
$cshowsPrec :: Int -> Certificate -> ShowS
Show, Certificate -> Certificate -> Bool
(Certificate -> Certificate -> Bool)
-> (Certificate -> Certificate -> Bool) -> Eq Certificate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Certificate -> Certificate -> Bool
$c/= :: Certificate -> Certificate -> Bool
== :: Certificate -> Certificate -> Bool
$c== :: Certificate -> Certificate -> Bool
Eq, (forall x. Certificate -> Rep Certificate x)
-> (forall x. Rep Certificate x -> Certificate)
-> Generic Certificate
forall x. Rep Certificate x -> Certificate
forall x. Certificate -> Rep Certificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Certificate x -> Certificate
$cfrom :: forall x. Certificate -> Rep Certificate x
Generic)
deriving anyclass ([Certificate] -> Encoding
[Certificate] -> Value
Certificate -> Encoding
Certificate -> Value
(Certificate -> Value)
-> (Certificate -> Encoding)
-> ([Certificate] -> Value)
-> ([Certificate] -> Encoding)
-> ToJSON Certificate
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Certificate] -> Encoding
$ctoEncodingList :: [Certificate] -> Encoding
toJSONList :: [Certificate] -> Value
$ctoJSONList :: [Certificate] -> Value
toEncoding :: Certificate -> Encoding
$ctoEncoding :: Certificate -> Encoding
toJSON :: Certificate -> Value
$ctoJSON :: Certificate -> Value
ToJSON, Value -> Parser [Certificate]
Value -> Parser Certificate
(Value -> Parser Certificate)
-> (Value -> Parser [Certificate]) -> FromJSON Certificate
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Certificate]
$cparseJSONList :: Value -> Parser [Certificate]
parseJSON :: Value -> Parser Certificate
$cparseJSON :: Value -> Parser Certificate
FromJSON, [Certificate] -> Encoding
Certificate -> Encoding
(Certificate -> Encoding)
-> (forall s. Decoder s Certificate)
-> ([Certificate] -> Encoding)
-> (forall s. Decoder s [Certificate])
-> Serialise Certificate
forall s. Decoder s [Certificate]
forall s. Decoder s Certificate
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
decodeList :: Decoder s [Certificate]
$cdecodeList :: forall s. Decoder s [Certificate]
encodeList :: [Certificate] -> Encoding
$cencodeList :: [Certificate] -> Encoding
decode :: Decoder s Certificate
$cdecode :: forall s. Decoder s Certificate
encode :: Certificate -> Encoding
$cencode :: Certificate -> Encoding
Serialise, Certificate -> ()
(Certificate -> ()) -> NFData Certificate
forall a. (a -> ()) -> NFData a
rnf :: Certificate -> ()
$crnf :: Certificate -> ()
NFData)
instance Pretty Certificate where
pretty :: Certificate -> Doc ann
pretty = Certificate -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow
inScripts :: TxIn -> Maybe (Versioned Validator, Redeemer, Maybe Datum)
inScripts :: TxIn -> Maybe (Versioned Validator, Redeemer, Maybe Datum)
inScripts TxIn{ txInType :: TxIn -> Maybe TxInType
txInType = Maybe TxInType
t } = case Maybe TxInType
t of
Just (ScriptAddress (Left Versioned Validator
v) Redeemer
r Maybe Datum
d) -> (Versioned Validator, Redeemer, Maybe Datum)
-> Maybe (Versioned Validator, Redeemer, Maybe Datum)
forall a. a -> Maybe a
Just (Versioned Validator
v, Redeemer
r, Maybe Datum
d)
Maybe TxInType
_ -> Maybe (Versioned Validator, Redeemer, Maybe Datum)
forall a. Maybe a
Nothing
inRef :: L.Lens' TxInput TxOutRef
inRef :: (TxOutRef -> f TxOutRef) -> TxInput -> f TxInput
inRef = (TxInput -> TxOutRef)
-> (TxInput -> TxOutRef -> TxInput)
-> Lens TxInput TxInput TxOutRef TxOutRef
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens TxInput -> TxOutRef
txInputRef TxInput -> TxOutRef -> TxInput
s where
s :: TxInput -> TxOutRef -> TxInput
s TxInput
txi TxOutRef
r = TxInput
txi { txInputRef :: TxOutRef
txInputRef = TxOutRef
r }
inType :: L.Lens' TxInput TxInputType
inType :: (TxInputType -> f TxInputType) -> TxInput -> f TxInput
inType = (TxInput -> TxInputType)
-> (TxInput -> TxInputType -> TxInput)
-> Lens TxInput TxInput TxInputType TxInputType
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens TxInput -> TxInputType
txInputType TxInput -> TxInputType -> TxInput
s where
s :: TxInput -> TxInputType -> TxInput
s TxInput
txi TxInputType
t = TxInput
txi { txInputType :: TxInputType
txInputType = TxInputType
t }
pubKeyTxInputs :: L.Fold [TxInput] TxInput
pubKeyTxInputs :: (TxInput -> f TxInput) -> [TxInput] -> f [TxInput]
pubKeyTxInputs = ([TxInput] -> [TxInput]) -> Fold [TxInput] TxInput
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
L.folding ((TxInput -> Bool) -> [TxInput] -> [TxInput]
forall a. (a -> Bool) -> [a] -> [a]
filter (\TxInput{ txInputType :: TxInput -> TxInputType
txInputType = TxInputType
t } -> TxInputType
t TxInputType -> TxInputType -> Bool
forall a. Eq a => a -> a -> Bool
== TxInputType
TxConsumePublicKeyAddress))
scriptTxInputs :: L.Fold [TxInput] TxInput
scriptTxInputs :: (TxInput -> f TxInput) -> [TxInput] -> f [TxInput]
scriptTxInputs = (\[TxInput] -> [TxInput]
x -> ([TxInput] -> [TxInput]) -> Fold [TxInput] TxInput
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
L.folding [TxInput] -> [TxInput]
x) (([TxInput] -> [TxInput])
-> (TxInput -> f TxInput) -> [TxInput] -> f [TxInput])
-> ((TxInput -> Bool) -> [TxInput] -> [TxInput])
-> (TxInput -> Bool)
-> (TxInput -> f TxInput)
-> [TxInput]
-> f [TxInput]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxInput -> Bool) -> [TxInput] -> [TxInput]
forall a. (a -> Bool) -> [a] -> [a]
filter ((TxInput -> Bool)
-> (TxInput -> f TxInput) -> [TxInput] -> f [TxInput])
-> (TxInput -> Bool)
-> (TxInput -> f TxInput)
-> [TxInput]
-> f [TxInput]
forall a b. (a -> b) -> a -> b
$ \case
TxInput{ txInputType :: TxInput -> TxInputType
txInputType = TxScriptAddress{} } -> Bool
True
TxInput
_ -> Bool
False
referenceScriptTxInputs :: L.Fold [TxInput] TxInput
referenceScriptTxInputs :: (TxInput -> f TxInput) -> [TxInput] -> f [TxInput]
referenceScriptTxInputs = (\[TxInput] -> [TxInput]
x -> ([TxInput] -> [TxInput]) -> Fold [TxInput] TxInput
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
L.folding [TxInput] -> [TxInput]
x) (([TxInput] -> [TxInput])
-> (TxInput -> f TxInput) -> [TxInput] -> f [TxInput])
-> ((TxInput -> Bool) -> [TxInput] -> [TxInput])
-> (TxInput -> Bool)
-> (TxInput -> f TxInput)
-> [TxInput]
-> f [TxInput]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxInput -> Bool) -> [TxInput] -> [TxInput]
forall a. (a -> Bool) -> [a] -> [a]
filter ((TxInput -> Bool)
-> (TxInput -> f TxInput) -> [TxInput] -> f [TxInput])
-> (TxInput -> Bool)
-> (TxInput -> f TxInput)
-> [TxInput]
-> f [TxInput]
forall a b. (a -> b) -> a -> b
$ \case
TxInput{ txInputType :: TxInput -> TxInputType
txInputType = TxScriptAddress Redeemer
_ (Right Versioned TxOutRef
_) Maybe DatumHash
_ } -> Bool
True
TxInput
_ -> Bool
False
newtype TxOut = TxOut {TxOut -> TxOut CtxTx BabbageEra
getTxOut :: C.TxOut C.CtxTx C.BabbageEra}
deriving stock (Int -> TxOut -> ShowS
[TxOut] -> ShowS
TxOut -> String
(Int -> TxOut -> ShowS)
-> (TxOut -> String) -> ([TxOut] -> ShowS) -> Show TxOut
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxOut] -> ShowS
$cshowList :: [TxOut] -> ShowS
show :: TxOut -> String
$cshow :: TxOut -> String
showsPrec :: Int -> TxOut -> ShowS
$cshowsPrec :: Int -> TxOut -> ShowS
Show, TxOut -> TxOut -> Bool
(TxOut -> TxOut -> Bool) -> (TxOut -> TxOut -> Bool) -> Eq TxOut
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxOut -> TxOut -> Bool
$c/= :: TxOut -> TxOut -> Bool
== :: TxOut -> TxOut -> Bool
$c== :: TxOut -> TxOut -> Bool
Eq, (forall x. TxOut -> Rep TxOut x)
-> (forall x. Rep TxOut x -> TxOut) -> Generic TxOut
forall x. Rep TxOut x -> TxOut
forall x. TxOut -> Rep TxOut x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxOut x -> TxOut
$cfrom :: forall x. TxOut -> Rep TxOut x
Generic)
deriving anyclass ([TxOut] -> Encoding
[TxOut] -> Value
TxOut -> Encoding
TxOut -> Value
(TxOut -> Value)
-> (TxOut -> Encoding)
-> ([TxOut] -> Value)
-> ([TxOut] -> Encoding)
-> ToJSON TxOut
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TxOut] -> Encoding
$ctoEncodingList :: [TxOut] -> Encoding
toJSONList :: [TxOut] -> Value
$ctoJSONList :: [TxOut] -> Value
toEncoding :: TxOut -> Encoding
$ctoEncoding :: TxOut -> Encoding
toJSON :: TxOut -> Value
$ctoJSON :: TxOut -> Value
ToJSON, Value -> Parser [TxOut]
Value -> Parser TxOut
(Value -> Parser TxOut)
-> (Value -> Parser [TxOut]) -> FromJSON TxOut
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TxOut]
$cparseJSONList :: Value -> Parser [TxOut]
parseJSON :: Value -> Parser TxOut
$cparseJSON :: Value -> Parser TxOut
FromJSON)
instance C.ToCBOR TxOut where
toCBOR :: TxOut -> Encoding
toCBOR (TxOut TxOut CtxTx BabbageEra
txout) = TxOut (BabbageEra StandardCrypto) -> Encoding
forall a. ToCBOR a => a -> Encoding
C.toCBOR (TxOut (BabbageEra StandardCrypto) -> Encoding)
-> TxOut (BabbageEra StandardCrypto) -> Encoding
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra BabbageEra
-> TxOut CtxTx BabbageEra -> TxOut (BabbageEra StandardCrypto)
forall era ledgerera.
(ShelleyLedgerEra era ~ ledgerera, IsShelleyBasedEra era) =>
ShelleyBasedEra era -> TxOut CtxTx era -> TxOut ledgerera
C.toShelleyTxOut ShelleyBasedEra BabbageEra
C.ShelleyBasedEraBabbage TxOut CtxTx BabbageEra
txout
instance C.FromCBOR TxOut where
fromCBOR :: Decoder s TxOut
fromCBOR = do
TxOut (BabbageEra StandardCrypto)
txout <- Decoder s (TxOut (BabbageEra StandardCrypto))
forall a s. FromCBOR a => Decoder s a
C.fromCBOR
TxOut -> Decoder s TxOut
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TxOut -> Decoder s TxOut) -> TxOut -> Decoder s TxOut
forall a b. (a -> b) -> a -> b
$ TxOut CtxTx BabbageEra -> TxOut
TxOut (TxOut CtxTx BabbageEra -> TxOut)
-> TxOut CtxTx BabbageEra -> TxOut
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra BabbageEra
-> TxOut (BabbageEra StandardCrypto) -> TxOut CtxTx BabbageEra
forall era ledgerera ctx.
(ShelleyLedgerEra era ~ ledgerera) =>
ShelleyBasedEra era -> TxOut ledgerera -> TxOut ctx era
C.fromShelleyTxOut ShelleyBasedEra BabbageEra
C.ShelleyBasedEraBabbage TxOut (BabbageEra StandardCrypto)
TxOut (BabbageEra StandardCrypto)
txout
instance Serialise TxOut where
encode :: TxOut -> Encoding
encode = TxOut -> Encoding
forall a. ToCBOR a => a -> Encoding
C.toCBOR
decode :: Decoder s TxOut
decode = Decoder s TxOut
forall a s. FromCBOR a => Decoder s a
C.fromCBOR
instance NFData TxOut where
rnf :: TxOut -> ()
rnf (TxOut TxOut CtxTx BabbageEra
tx) = TxOut CtxTx BabbageEra -> () -> ()
seq TxOut CtxTx BabbageEra
tx ()
instance OpenApi.ToSchema TxOut where
declareNamedSchema :: Proxy TxOut -> Declare (Definitions Schema) NamedSchema
declareNamedSchema Proxy TxOut
_ = do
Referenced Schema
addressSchema <- Proxy (AddressInEra BabbageEra)
-> Declare (Definitions Schema) (Referenced Schema)
forall a.
ToSchema a =>
Proxy a -> Declare (Definitions Schema) (Referenced Schema)
OpenApi.declareSchemaRef (Proxy (AddressInEra BabbageEra)
forall k (t :: k). Proxy t
Proxy :: Proxy (C.AddressInEra C.BabbageEra))
Referenced Schema
valueSchema <- Proxy Value -> Declare (Definitions Schema) (Referenced Schema)
forall a.
ToSchema a =>
Proxy a -> Declare (Definitions Schema) (Referenced Schema)
OpenApi.declareSchemaRef (Proxy Value
forall k (t :: k). Proxy t
Proxy :: Proxy Value)
Referenced Schema
bsSchema <- Proxy Datum -> Declare (Definitions Schema) (Referenced Schema)
forall a.
ToSchema a =>
Proxy a -> Declare (Definitions Schema) (Referenced Schema)
OpenApi.declareSchemaRef (Proxy Datum
forall k (t :: k). Proxy t
Proxy :: Proxy Datum)
NamedSchema -> Declare (Definitions Schema) NamedSchema
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NamedSchema -> Declare (Definitions Schema) NamedSchema)
-> NamedSchema -> Declare (Definitions Schema) NamedSchema
forall a b. (a -> b) -> a -> b
$ Maybe Text -> Schema -> NamedSchema
OpenApi.NamedSchema (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"TxOut") (Schema -> NamedSchema) -> Schema -> NamedSchema
forall a b. (a -> b) -> a -> b
$ Schema
forall a. Monoid a => a
mempty
Schema -> (Schema -> Schema) -> Schema
forall a b. a -> (a -> b) -> b
& (Maybe OpenApiType -> Identity (Maybe OpenApiType))
-> Schema -> Identity Schema
forall s a. HasType s a => Lens' s a
OpenApi.type_ ((Maybe OpenApiType -> Identity (Maybe OpenApiType))
-> Schema -> Identity Schema)
-> OpenApiType -> Schema -> Schema
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApi.OpenApiObject
Schema -> (Schema -> Schema) -> Schema
forall a b. a -> (a -> b) -> b
& (InsOrdHashMap Text (Referenced Schema)
-> Identity (InsOrdHashMap Text (Referenced Schema)))
-> Schema -> Identity Schema
forall s a. HasProperties s a => Lens' s a
OpenApi.properties ((InsOrdHashMap Text (Referenced Schema)
-> Identity (InsOrdHashMap Text (Referenced Schema)))
-> Schema -> Identity Schema)
-> InsOrdHashMap Text (Referenced Schema) -> Schema -> Schema
forall s t a b. ASetter s t a b -> b -> s -> t
.~
[ (Text
"address", Referenced Schema
addressSchema)
, (Text
"value", Referenced Schema
valueSchema)
, (Text
"datum", Referenced Schema
bsSchema)
, (Text
"referenceScript", Referenced Schema
bsSchema)
]
Schema -> (Schema -> Schema) -> Schema
forall a b. a -> (a -> b) -> b
& ([Text] -> Identity [Text]) -> Schema -> Identity Schema
forall s a. HasRequired s a => Lens' s a
OpenApi.required (([Text] -> Identity [Text]) -> Schema -> Identity Schema)
-> [Text] -> Schema -> Schema
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Item [Text]
"address",Item [Text]
"value"]
instance Pretty TxOut where
pretty :: TxOut -> Doc ann
pretty (TxOut (C.TxOut AddressInEra BabbageEra
addr TxOutValue BabbageEra
v TxOutDatum CtxTx BabbageEra
d ReferenceScript BabbageEra
rs)) =
Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$
[Doc ann
"-" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (TxOutValue BabbageEra -> Value
forall era. TxOutValue era -> Value
fromCardanoTxOutValue TxOutValue BabbageEra
v) Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
"addressed to"
, Address -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (AddressInEra BabbageEra -> Address
forall era. AddressInEra era -> Address
toPlutusAddress AddressInEra BabbageEra
addr)
]
[Doc ann] -> [Doc ann] -> [Doc ann]
forall a. Semigroup a => a -> a -> a
<> case TxOutDatum CtxTx BabbageEra -> OutputDatum
forall era. TxOutDatum CtxTx era -> OutputDatum
fromCardanoTxOutDatum TxOutDatum CtxTx BabbageEra
d of
OutputDatum
PV2.NoOutputDatum -> []
PV2.OutputDatum Datum
dv -> [Doc ann
"with inline datum" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Datum -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow Datum
dv]
PV2.OutputDatumHash DatumHash
dh -> [Doc ann
"with datum hash" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> DatumHash -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty DatumHash
dh]
[Doc ann] -> [Doc ann] -> [Doc ann]
forall a. Semigroup a => a -> a -> a
<> case ReferenceScript BabbageEra
rs of
C.ReferenceScript ReferenceTxInsScriptsInlineDatumsSupportedInEra BabbageEra
_ (C.ScriptInAnyLang ScriptLanguage lang
_ Script lang
s) ->
[Doc ann
"with reference script hash" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> ScriptHash -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow (Script lang -> ScriptHash
forall lang. Script lang -> ScriptHash
C.hashScript Script lang
s)]
ReferenceScript BabbageEra
C.ReferenceScriptNone -> []
toSizedTxOut :: TxOut -> Ledger.Sized (Ledger.TxOut Ledger.StandardBabbage)
toSizedTxOut :: TxOut -> Sized (TxOut (BabbageEra StandardCrypto))
toSizedTxOut = TxOut (BabbageEra StandardCrypto)
-> Sized (TxOut (BabbageEra StandardCrypto))
forall a. ToCBOR a => a -> Sized a
Ledger.mkSized (TxOut (BabbageEra StandardCrypto)
-> Sized (TxOut (BabbageEra StandardCrypto)))
-> (TxOut -> TxOut (BabbageEra StandardCrypto))
-> TxOut
-> Sized (TxOut (BabbageEra StandardCrypto))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShelleyBasedEra BabbageEra
-> TxOut CtxTx BabbageEra -> TxOut (BabbageEra StandardCrypto)
forall era ledgerera.
(ShelleyLedgerEra era ~ ledgerera, IsShelleyBasedEra era) =>
ShelleyBasedEra era -> TxOut CtxTx era -> TxOut ledgerera
C.toShelleyTxOut ShelleyBasedEra BabbageEra
C.ShelleyBasedEraBabbage (TxOut CtxTx BabbageEra -> TxOut (BabbageEra StandardCrypto))
-> (TxOut -> TxOut CtxTx BabbageEra)
-> TxOut
-> TxOut (BabbageEra StandardCrypto)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOut -> TxOut CtxTx BabbageEra
getTxOut
type ScriptsMap = Map ScriptHash (Versioned Script)
type MintingWitnessesMap = Map MintingPolicyHash (Redeemer, Maybe (Versioned TxOutRef))
data Tx = Tx {
Tx -> [TxInput]
txInputs :: [TxInput],
Tx -> [TxInput]
txReferenceInputs :: [TxInput],
Tx -> [TxInput]
txCollateralInputs :: [TxInput],
Tx -> [TxOut]
txOutputs :: [TxOut],
Tx -> Maybe TxOut
txReturnCollateral :: Maybe TxOut,
Tx -> Maybe Value
txTotalCollateral :: Maybe Value,
Tx -> Value
txMint :: !Value,
Tx -> Value
txFee :: !Value,
Tx -> SlotRange
txValidRange :: !SlotRange,
Tx -> MintingWitnessesMap
txMintingWitnesses :: MintingWitnessesMap,
Tx -> [Withdrawal]
txWithdrawals :: [Withdrawal],
Tx -> [Certificate]
txCertificates :: [Certificate],
Tx -> Map PubKey Signature
txSignatures :: Map PubKey Signature,
Tx -> ScriptsMap
txScripts :: ScriptsMap,
Tx -> Map DatumHash Datum
txData :: Map DatumHash Datum,
Tx -> Maybe BuiltinByteString
txMetadata :: Maybe BuiltinByteString
} deriving stock (Int -> Tx -> ShowS
[Tx] -> ShowS
Tx -> String
(Int -> Tx -> ShowS)
-> (Tx -> String) -> ([Tx] -> ShowS) -> Show Tx
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tx] -> ShowS
$cshowList :: [Tx] -> ShowS
show :: Tx -> String
$cshow :: Tx -> String
showsPrec :: Int -> Tx -> ShowS
$cshowsPrec :: Int -> Tx -> ShowS
Show, Tx -> Tx -> Bool
(Tx -> Tx -> Bool) -> (Tx -> Tx -> Bool) -> Eq Tx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tx -> Tx -> Bool
$c/= :: Tx -> Tx -> Bool
== :: Tx -> Tx -> Bool
$c== :: Tx -> Tx -> Bool
Eq, (forall x. Tx -> Rep Tx x)
-> (forall x. Rep Tx x -> Tx) -> Generic Tx
forall x. Rep Tx x -> Tx
forall x. Tx -> Rep Tx x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Tx x -> Tx
$cfrom :: forall x. Tx -> Rep Tx x
Generic)
deriving anyclass ([Tx] -> Encoding
[Tx] -> Value
Tx -> Encoding
Tx -> Value
(Tx -> Value)
-> (Tx -> Encoding)
-> ([Tx] -> Value)
-> ([Tx] -> Encoding)
-> ToJSON Tx
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Tx] -> Encoding
$ctoEncodingList :: [Tx] -> Encoding
toJSONList :: [Tx] -> Value
$ctoJSONList :: [Tx] -> Value
toEncoding :: Tx -> Encoding
$ctoEncoding :: Tx -> Encoding
toJSON :: Tx -> Value
$ctoJSON :: Tx -> Value
ToJSON, Value -> Parser [Tx]
Value -> Parser Tx
(Value -> Parser Tx) -> (Value -> Parser [Tx]) -> FromJSON Tx
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Tx]
$cparseJSONList :: Value -> Parser [Tx]
parseJSON :: Value -> Parser Tx
$cparseJSON :: Value -> Parser Tx
FromJSON, [Tx] -> Encoding
Tx -> Encoding
(Tx -> Encoding)
-> (forall s. Decoder s Tx)
-> ([Tx] -> Encoding)
-> (forall s. Decoder s [Tx])
-> Serialise Tx
forall s. Decoder s [Tx]
forall s. Decoder s Tx
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
decodeList :: Decoder s [Tx]
$cdecodeList :: forall s. Decoder s [Tx]
encodeList :: [Tx] -> Encoding
$cencodeList :: [Tx] -> Encoding
decode :: Decoder s Tx
$cdecode :: forall s. Decoder s Tx
encode :: Tx -> Encoding
$cencode :: Tx -> Encoding
Serialise, Tx -> ()
(Tx -> ()) -> NFData Tx
forall a. (a -> ()) -> NFData a
rnf :: Tx -> ()
$crnf :: Tx -> ()
NFData)
instance Semigroup Tx where
Tx
tx1 <> :: Tx -> Tx -> Tx
<> Tx
tx2 = Tx :: [TxInput]
-> [TxInput]
-> [TxInput]
-> [TxOut]
-> Maybe TxOut
-> Maybe Value
-> Value
-> Value
-> SlotRange
-> MintingWitnessesMap
-> [Withdrawal]
-> [Certificate]
-> Map PubKey Signature
-> ScriptsMap
-> Map DatumHash Datum
-> Maybe BuiltinByteString
-> Tx
Tx {
txInputs :: [TxInput]
txInputs = Tx -> [TxInput]
txInputs Tx
tx1 [TxInput] -> [TxInput] -> [TxInput]
forall a. Semigroup a => a -> a -> a
<> Tx -> [TxInput]
txInputs Tx
tx2,
txReferenceInputs :: [TxInput]
txReferenceInputs = Tx -> [TxInput]
txReferenceInputs Tx
tx1 [TxInput] -> [TxInput] -> [TxInput]
forall a. Semigroup a => a -> a -> a
<> Tx -> [TxInput]
txReferenceInputs Tx
tx2,
txCollateralInputs :: [TxInput]
txCollateralInputs = Tx -> [TxInput]
txCollateralInputs Tx
tx1 [TxInput] -> [TxInput] -> [TxInput]
forall a. Semigroup a => a -> a -> a
<> Tx -> [TxInput]
txCollateralInputs Tx
tx2,
txOutputs :: [TxOut]
txOutputs = Tx -> [TxOut]
txOutputs Tx
tx1 [TxOut] -> [TxOut] -> [TxOut]
forall a. Semigroup a => a -> a -> a
<> Tx -> [TxOut]
txOutputs Tx
tx2,
txReturnCollateral :: Maybe TxOut
txReturnCollateral = Tx -> Maybe TxOut
txReturnCollateral Tx
tx1 Maybe TxOut -> Maybe TxOut -> Maybe TxOut
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Tx -> Maybe TxOut
txReturnCollateral Tx
tx2,
txTotalCollateral :: Maybe Value
txTotalCollateral = Tx -> Maybe Value
txTotalCollateral Tx
tx1 Maybe Value -> Maybe Value -> Maybe Value
forall a. Semigroup a => a -> a -> a
<> Tx -> Maybe Value
txTotalCollateral Tx
tx2,
txMint :: Value
txMint = Tx -> Value
txMint Tx
tx1 Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Tx -> Value
txMint Tx
tx2,
txFee :: Value
txFee = Tx -> Value
txFee Tx
tx1 Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Tx -> Value
txFee Tx
tx2,
txValidRange :: SlotRange
txValidRange = Tx -> SlotRange
txValidRange Tx
tx1 SlotRange -> SlotRange -> SlotRange
forall a. MeetSemiLattice a => a -> a -> a
/\ Tx -> SlotRange
txValidRange Tx
tx2,
txMintingWitnesses :: MintingWitnessesMap
txMintingWitnesses = Tx -> MintingWitnessesMap
txMintingWitnesses Tx
tx1 MintingWitnessesMap -> MintingWitnessesMap -> MintingWitnessesMap
forall a. Semigroup a => a -> a -> a
<> Tx -> MintingWitnessesMap
txMintingWitnesses Tx
tx2,
txSignatures :: Map PubKey Signature
txSignatures = Tx -> Map PubKey Signature
txSignatures Tx
tx1 Map PubKey Signature
-> Map PubKey Signature -> Map PubKey Signature
forall a. Semigroup a => a -> a -> a
<> Tx -> Map PubKey Signature
txSignatures Tx
tx2,
txData :: Map DatumHash Datum
txData = Tx -> Map DatumHash Datum
txData Tx
tx1 Map DatumHash Datum -> Map DatumHash Datum -> Map DatumHash Datum
forall a. Semigroup a => a -> a -> a
<> Tx -> Map DatumHash Datum
txData Tx
tx2,
txScripts :: ScriptsMap
txScripts = Tx -> ScriptsMap
txScripts Tx
tx1 ScriptsMap -> ScriptsMap -> ScriptsMap
forall a. Semigroup a => a -> a -> a
<> Tx -> ScriptsMap
txScripts Tx
tx2,
txWithdrawals :: [Withdrawal]
txWithdrawals = Tx -> [Withdrawal]
txWithdrawals Tx
tx1 [Withdrawal] -> [Withdrawal] -> [Withdrawal]
forall a. Semigroup a => a -> a -> a
<> Tx -> [Withdrawal]
txWithdrawals Tx
tx2,
txCertificates :: [Certificate]
txCertificates = Tx -> [Certificate]
txCertificates Tx
tx1 [Certificate] -> [Certificate] -> [Certificate]
forall a. Semigroup a => a -> a -> a
<> Tx -> [Certificate]
txCertificates Tx
tx2,
txMetadata :: Maybe BuiltinByteString
txMetadata = Tx -> Maybe BuiltinByteString
txMetadata Tx
tx1 Maybe BuiltinByteString
-> Maybe BuiltinByteString -> Maybe BuiltinByteString
forall a. Semigroup a => a -> a -> a
<> Tx -> Maybe BuiltinByteString
txMetadata Tx
tx2
}
instance Monoid Tx where
mempty :: Tx
mempty = [TxInput]
-> [TxInput]
-> [TxInput]
-> [TxOut]
-> Maybe TxOut
-> Maybe Value
-> Value
-> Value
-> SlotRange
-> MintingWitnessesMap
-> [Withdrawal]
-> [Certificate]
-> Map PubKey Signature
-> ScriptsMap
-> Map DatumHash Datum
-> Maybe BuiltinByteString
-> Tx
Tx [TxInput]
forall a. Monoid a => a
mempty [TxInput]
forall a. Monoid a => a
mempty [TxInput]
forall a. Monoid a => a
mempty [TxOut]
forall a. Monoid a => a
mempty Maybe TxOut
forall (f :: * -> *) a. Alternative f => f a
empty Maybe Value
forall a. Monoid a => a
mempty Value
forall a. Monoid a => a
mempty Value
forall a. Monoid a => a
mempty SlotRange
forall a. BoundedMeetSemiLattice a => a
top MintingWitnessesMap
forall a. Monoid a => a
mempty [Withdrawal]
forall a. Monoid a => a
mempty [Certificate]
forall a. Monoid a => a
mempty Map PubKey Signature
forall a. Monoid a => a
mempty ScriptsMap
forall a. Monoid a => a
mempty Map DatumHash Datum
forall a. Monoid a => a
mempty Maybe BuiltinByteString
forall a. Monoid a => a
mempty
instance BA.ByteArrayAccess Tx where
length :: Tx -> Int
length = ByteString -> Int
forall ba. ByteArrayAccess ba => ba -> Int
BA.length (ByteString -> Int) -> (Tx -> ByteString) -> Tx -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Encoding -> ByteString
Write.toStrictByteString (Encoding -> ByteString) -> (Tx -> Encoding) -> Tx -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tx -> Encoding
forall a. Serialise a => a -> Encoding
encode
withByteArray :: Tx -> (Ptr p -> IO a) -> IO a
withByteArray = ByteString -> (Ptr p -> IO a) -> IO a
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
BA.withByteArray (ByteString -> (Ptr p -> IO a) -> IO a)
-> (Tx -> ByteString) -> Tx -> (Ptr p -> IO a) -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Encoding -> ByteString
Write.toStrictByteString (Encoding -> ByteString) -> (Tx -> Encoding) -> Tx -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tx -> Encoding
forall a. Serialise a => a -> Encoding
encode
inputs :: L.Lens' Tx [TxInput]
inputs :: ([TxInput] -> f [TxInput]) -> Tx -> f Tx
inputs = (Tx -> [TxInput])
-> (Tx -> [TxInput] -> Tx) -> Lens Tx Tx [TxInput] [TxInput]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> [TxInput]
g Tx -> [TxInput] -> Tx
s where
g :: Tx -> [TxInput]
g = Tx -> [TxInput]
txInputs
s :: Tx -> [TxInput] -> Tx
s Tx
tx [TxInput]
i = Tx
tx { txInputs :: [TxInput]
txInputs = [TxInput]
i }
referenceInputs :: L.Lens' Tx [TxInput]
referenceInputs :: ([TxInput] -> f [TxInput]) -> Tx -> f Tx
referenceInputs = (Tx -> [TxInput])
-> (Tx -> [TxInput] -> Tx) -> Lens Tx Tx [TxInput] [TxInput]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> [TxInput]
g Tx -> [TxInput] -> Tx
s where
g :: Tx -> [TxInput]
g = Tx -> [TxInput]
txReferenceInputs
s :: Tx -> [TxInput] -> Tx
s Tx
tx [TxInput]
i = Tx
tx { txReferenceInputs :: [TxInput]
txReferenceInputs = [TxInput]
i }
collateralInputs :: L.Lens' Tx [TxInput]
collateralInputs :: ([TxInput] -> f [TxInput]) -> Tx -> f Tx
collateralInputs = (Tx -> [TxInput])
-> (Tx -> [TxInput] -> Tx) -> Lens Tx Tx [TxInput] [TxInput]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> [TxInput]
g Tx -> [TxInput] -> Tx
s where
g :: Tx -> [TxInput]
g = Tx -> [TxInput]
txCollateralInputs
s :: Tx -> [TxInput] -> Tx
s Tx
tx [TxInput]
i = Tx
tx { txCollateralInputs :: [TxInput]
txCollateralInputs = [TxInput]
i }
outputs :: L.Lens' Tx [TxOut]
outputs :: ([TxOut] -> f [TxOut]) -> Tx -> f Tx
outputs = (Tx -> [TxOut])
-> (Tx -> [TxOut] -> Tx) -> Lens Tx Tx [TxOut] [TxOut]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> [TxOut]
g Tx -> [TxOut] -> Tx
s where
g :: Tx -> [TxOut]
g = Tx -> [TxOut]
txOutputs
s :: Tx -> [TxOut] -> Tx
s Tx
tx [TxOut]
o = Tx
tx { txOutputs :: [TxOut]
txOutputs = [TxOut]
o }
returnCollateral :: L.Lens' Tx (Maybe TxOut)
returnCollateral :: (Maybe TxOut -> f (Maybe TxOut)) -> Tx -> f Tx
returnCollateral = (Tx -> Maybe TxOut)
-> (Tx -> Maybe TxOut -> Tx)
-> Lens Tx Tx (Maybe TxOut) (Maybe TxOut)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> Maybe TxOut
g Tx -> Maybe TxOut -> Tx
s where
g :: Tx -> Maybe TxOut
g = Tx -> Maybe TxOut
txReturnCollateral
s :: Tx -> Maybe TxOut -> Tx
s Tx
tx Maybe TxOut
o = Tx
tx { txReturnCollateral :: Maybe TxOut
txReturnCollateral = Maybe TxOut
o }
totalCollateral :: L.Lens' Tx (Maybe Value)
totalCollateral :: (Maybe Value -> f (Maybe Value)) -> Tx -> f Tx
totalCollateral = (Tx -> Maybe Value)
-> (Tx -> Maybe Value -> Tx)
-> Lens Tx Tx (Maybe Value) (Maybe Value)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> Maybe Value
g Tx -> Maybe Value -> Tx
s where
g :: Tx -> Maybe Value
g = Tx -> Maybe Value
txTotalCollateral
s :: Tx -> Maybe Value -> Tx
s Tx
tx Maybe Value
o = Tx
tx { txTotalCollateral :: Maybe Value
txTotalCollateral = Maybe Value
o }
validRange :: L.Lens' Tx SlotRange
validRange :: (SlotRange -> f SlotRange) -> Tx -> f Tx
validRange = (Tx -> SlotRange)
-> (Tx -> SlotRange -> Tx) -> Lens Tx Tx SlotRange SlotRange
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> SlotRange
g Tx -> SlotRange -> Tx
s where
g :: Tx -> SlotRange
g = Tx -> SlotRange
txValidRange
s :: Tx -> SlotRange -> Tx
s Tx
tx SlotRange
o = Tx
tx { txValidRange :: SlotRange
txValidRange = SlotRange
o }
signatures :: L.Lens' Tx (Map PubKey Signature)
signatures :: (Map PubKey Signature -> f (Map PubKey Signature)) -> Tx -> f Tx
signatures = (Tx -> Map PubKey Signature)
-> (Tx -> Map PubKey Signature -> Tx)
-> Lens Tx Tx (Map PubKey Signature) (Map PubKey Signature)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> Map PubKey Signature
g Tx -> Map PubKey Signature -> Tx
s where
g :: Tx -> Map PubKey Signature
g = Tx -> Map PubKey Signature
txSignatures
s :: Tx -> Map PubKey Signature -> Tx
s Tx
tx Map PubKey Signature
sig = Tx
tx { txSignatures :: Map PubKey Signature
txSignatures = Map PubKey Signature
sig }
fee :: L.Lens' Tx Value
fee :: (Value -> f Value) -> Tx -> f Tx
fee = (Tx -> Value) -> (Tx -> Value -> Tx) -> Lens Tx Tx Value Value
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> Value
g Tx -> Value -> Tx
s where
g :: Tx -> Value
g = Tx -> Value
txFee
s :: Tx -> Value -> Tx
s Tx
tx Value
v = Tx
tx { txFee :: Value
txFee = Value
v }
mint :: L.Lens' Tx Value
mint :: (Value -> f Value) -> Tx -> f Tx
mint = (Tx -> Value) -> (Tx -> Value -> Tx) -> Lens Tx Tx Value Value
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> Value
g Tx -> Value -> Tx
s where
g :: Tx -> Value
g = Tx -> Value
txMint
s :: Tx -> Value -> Tx
s Tx
tx Value
v = Tx
tx { txMint :: Value
txMint = Value
v }
mintScripts :: L.Lens' Tx MintingWitnessesMap
mintScripts :: (MintingWitnessesMap -> f MintingWitnessesMap) -> Tx -> f Tx
mintScripts = (Tx -> MintingWitnessesMap)
-> (Tx -> MintingWitnessesMap -> Tx)
-> Lens Tx Tx MintingWitnessesMap MintingWitnessesMap
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> MintingWitnessesMap
g Tx -> MintingWitnessesMap -> Tx
s where
g :: Tx -> MintingWitnessesMap
g = Tx -> MintingWitnessesMap
txMintingWitnesses
s :: Tx -> MintingWitnessesMap -> Tx
s Tx
tx MintingWitnessesMap
fs = Tx
tx { txMintingWitnesses :: MintingWitnessesMap
txMintingWitnesses = MintingWitnessesMap
fs }
scriptWitnesses :: L.Lens' Tx ScriptsMap
scriptWitnesses :: (ScriptsMap -> f ScriptsMap) -> Tx -> f Tx
scriptWitnesses = (Tx -> ScriptsMap)
-> (Tx -> ScriptsMap -> Tx) -> Lens Tx Tx ScriptsMap ScriptsMap
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> ScriptsMap
g Tx -> ScriptsMap -> Tx
s where
g :: Tx -> ScriptsMap
g = Tx -> ScriptsMap
txScripts
s :: Tx -> ScriptsMap -> Tx
s Tx
tx ScriptsMap
fs = Tx
tx { txScripts :: ScriptsMap
txScripts = ScriptsMap
fs }
datumWitnesses :: L.Lens' Tx (Map DatumHash Datum)
datumWitnesses :: (Map DatumHash Datum -> f (Map DatumHash Datum)) -> Tx -> f Tx
datumWitnesses = (Tx -> Map DatumHash Datum)
-> (Tx -> Map DatumHash Datum -> Tx)
-> Lens Tx Tx (Map DatumHash Datum) (Map DatumHash Datum)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> Map DatumHash Datum
g Tx -> Map DatumHash Datum -> Tx
s where
g :: Tx -> Map DatumHash Datum
g = Tx -> Map DatumHash Datum
txData
s :: Tx -> Map DatumHash Datum -> Tx
s Tx
tx Map DatumHash Datum
dat = Tx
tx { txData :: Map DatumHash Datum
txData = Map DatumHash Datum
dat }
metadata :: L.Lens' Tx (Maybe BuiltinByteString)
metadata :: (Maybe BuiltinByteString -> f (Maybe BuiltinByteString))
-> Tx -> f Tx
metadata = (Tx -> Maybe BuiltinByteString)
-> (Tx -> Maybe BuiltinByteString -> Tx)
-> Lens Tx Tx (Maybe BuiltinByteString) (Maybe BuiltinByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens Tx -> Maybe BuiltinByteString
g Tx -> Maybe BuiltinByteString -> Tx
s where
g :: Tx -> Maybe BuiltinByteString
g = Tx -> Maybe BuiltinByteString
txMetadata
s :: Tx -> Maybe BuiltinByteString -> Tx
s Tx
tx Maybe BuiltinByteString
i = Tx
tx { txMetadata :: Maybe BuiltinByteString
txMetadata = Maybe BuiltinByteString
i }
lookupSignature :: PubKey -> Tx -> Maybe Signature
lookupSignature :: PubKey -> Tx -> Maybe Signature
lookupSignature PubKey
s Tx{Map PubKey Signature
txSignatures :: Map PubKey Signature
txSignatures :: Tx -> Map PubKey Signature
txSignatures} = PubKey -> Map PubKey Signature -> Maybe Signature
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup PubKey
s Map PubKey Signature
txSignatures
lookupDatum :: Tx -> DatumHash -> Maybe Datum
lookupDatum :: Tx -> DatumHash -> Maybe Datum
lookupDatum Tx{Map DatumHash Datum
txData :: Map DatumHash Datum
txData :: Tx -> Map DatumHash Datum
txData} DatumHash
h = DatumHash -> Map DatumHash Datum -> Maybe Datum
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup DatumHash
h Map DatumHash Datum
txData
validValuesTx :: Tx -> Bool
validValuesTx :: Tx -> Bool
validValuesTx Tx{[TxOut]
[Certificate]
[Withdrawal]
[TxInput]
Maybe Value
Maybe BuiltinByteString
Maybe TxOut
ScriptsMap
Map DatumHash Datum
MintingWitnessesMap
Map PubKey Signature
Value
SlotRange
txMetadata :: Maybe BuiltinByteString
txData :: Map DatumHash Datum
txScripts :: ScriptsMap
txSignatures :: Map PubKey Signature
txCertificates :: [Certificate]
txWithdrawals :: [Withdrawal]
txMintingWitnesses :: MintingWitnessesMap
txValidRange :: SlotRange
txFee :: Value
txMint :: Value
txTotalCollateral :: Maybe Value
txReturnCollateral :: Maybe TxOut
txOutputs :: [TxOut]
txCollateralInputs :: [TxInput]
txReferenceInputs :: [TxInput]
txInputs :: [TxInput]
txMetadata :: Tx -> Maybe BuiltinByteString
txData :: Tx -> Map DatumHash Datum
txScripts :: Tx -> ScriptsMap
txSignatures :: Tx -> Map PubKey Signature
txCertificates :: Tx -> [Certificate]
txWithdrawals :: Tx -> [Withdrawal]
txMintingWitnesses :: Tx -> MintingWitnessesMap
txValidRange :: Tx -> SlotRange
txFee :: Tx -> Value
txMint :: Tx -> Value
txTotalCollateral :: Tx -> Maybe Value
txReturnCollateral :: Tx -> Maybe TxOut
txOutputs :: Tx -> [TxOut]
txCollateralInputs :: Tx -> [TxInput]
txReferenceInputs :: Tx -> [TxInput]
txInputs :: Tx -> [TxInput]
..}
= (TxOut -> Bool) -> [TxOut] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Value -> Bool
nonNegative (Value -> Bool) -> (TxOut -> Value) -> TxOut -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOut -> Value
txOutValue) [TxOut]
txOutputs Bool -> Bool -> Bool
&& Value -> Bool
nonNegative Value
txFee
where
nonNegative :: Value -> Bool
nonNegative Value
i = Value -> Value -> Bool
V.geq Value
i Value
forall a. Monoid a => a
mempty
txOutValue :: TxOut -> Value
txOutValue :: TxOut -> Value
txOutValue (TxOut (C.TxOut AddressInEra BabbageEra
_aie TxOutValue BabbageEra
tov TxOutDatum CtxTx BabbageEra
_tod ReferenceScript BabbageEra
_rs)) =
Value -> Value
fromCardanoValue (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ TxOutValue BabbageEra -> Value
forall era. TxOutValue era -> Value
C.txOutValueToValue TxOutValue BabbageEra
tov
outValue :: L.Lens TxOut TxOut Value (C.TxOutValue C.BabbageEra)
outValue :: (Value -> f (TxOutValue BabbageEra)) -> TxOut -> f TxOut
outValue = (TxOut -> Value)
-> (TxOut -> TxOutValue BabbageEra -> TxOut)
-> Lens TxOut TxOut Value (TxOutValue BabbageEra)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens
TxOut -> Value
txOutValue
(\(TxOut (C.TxOut AddressInEra BabbageEra
aie TxOutValue BabbageEra
_ TxOutDatum CtxTx BabbageEra
tod ReferenceScript BabbageEra
rs)) TxOutValue BabbageEra
tov -> TxOut CtxTx BabbageEra -> TxOut
TxOut (AddressInEra BabbageEra
-> TxOutValue BabbageEra
-> TxOutDatum CtxTx BabbageEra
-> ReferenceScript BabbageEra
-> TxOut CtxTx BabbageEra
forall ctx era.
AddressInEra era
-> TxOutValue era
-> TxOutDatum ctx era
-> ReferenceScript era
-> TxOut ctx era
C.TxOut AddressInEra BabbageEra
aie TxOutValue BabbageEra
tov TxOutDatum CtxTx BabbageEra
tod ReferenceScript BabbageEra
rs))
outValue' :: L.Lens' TxOut (C.TxOutValue C.BabbageEra)
outValue' :: (TxOutValue BabbageEra -> f (TxOutValue BabbageEra))
-> TxOut -> f TxOut
outValue' = (TxOut -> TxOutValue BabbageEra)
-> (TxOut -> TxOutValue BabbageEra -> TxOut)
-> Lens TxOut TxOut (TxOutValue BabbageEra) (TxOutValue BabbageEra)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens
(\(TxOut (C.TxOut AddressInEra BabbageEra
_aie TxOutValue BabbageEra
tov TxOutDatum CtxTx BabbageEra
_tod ReferenceScript BabbageEra
_rs)) -> TxOutValue BabbageEra
tov)
(\(TxOut (C.TxOut AddressInEra BabbageEra
aie TxOutValue BabbageEra
_ TxOutDatum CtxTx BabbageEra
tod ReferenceScript BabbageEra
rs)) TxOutValue BabbageEra
tov -> TxOut CtxTx BabbageEra -> TxOut
TxOut (AddressInEra BabbageEra
-> TxOutValue BabbageEra
-> TxOutDatum CtxTx BabbageEra
-> ReferenceScript BabbageEra
-> TxOut CtxTx BabbageEra
forall ctx era.
AddressInEra era
-> TxOutValue era
-> TxOutDatum ctx era
-> ReferenceScript era
-> TxOut ctx era
C.TxOut AddressInEra BabbageEra
aie TxOutValue BabbageEra
tov TxOutDatum CtxTx BabbageEra
tod ReferenceScript BabbageEra
rs))
data TxStripped = TxStripped {
TxStripped -> [TxOutRef]
txStrippedInputs :: [TxOutRef],
TxStripped -> [TxOutRef]
txStrippedReferenceInputs :: [TxOutRef],
TxStripped -> [TxOut]
txStrippedOutputs :: [TxOut],
TxStripped -> Value
txStrippedMint :: !Value,
TxStripped -> Value
txStrippedFee :: !Value
} deriving (Int -> TxStripped -> ShowS
[TxStripped] -> ShowS
TxStripped -> String
(Int -> TxStripped -> ShowS)
-> (TxStripped -> String)
-> ([TxStripped] -> ShowS)
-> Show TxStripped
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxStripped] -> ShowS
$cshowList :: [TxStripped] -> ShowS
show :: TxStripped -> String
$cshow :: TxStripped -> String
showsPrec :: Int -> TxStripped -> ShowS
$cshowsPrec :: Int -> TxStripped -> ShowS
Show, TxStripped -> TxStripped -> Bool
(TxStripped -> TxStripped -> Bool)
-> (TxStripped -> TxStripped -> Bool) -> Eq TxStripped
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxStripped -> TxStripped -> Bool
$c/= :: TxStripped -> TxStripped -> Bool
== :: TxStripped -> TxStripped -> Bool
$c== :: TxStripped -> TxStripped -> Bool
Eq, (forall x. TxStripped -> Rep TxStripped x)
-> (forall x. Rep TxStripped x -> TxStripped) -> Generic TxStripped
forall x. Rep TxStripped x -> TxStripped
forall x. TxStripped -> Rep TxStripped x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxStripped x -> TxStripped
$cfrom :: forall x. TxStripped -> Rep TxStripped x
Generic, [TxStripped] -> Encoding
TxStripped -> Encoding
(TxStripped -> Encoding)
-> (forall s. Decoder s TxStripped)
-> ([TxStripped] -> Encoding)
-> (forall s. Decoder s [TxStripped])
-> Serialise TxStripped
forall s. Decoder s [TxStripped]
forall s. Decoder s TxStripped
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
decodeList :: Decoder s [TxStripped]
$cdecodeList :: forall s. Decoder s [TxStripped]
encodeList :: [TxStripped] -> Encoding
$cencodeList :: [TxStripped] -> Encoding
decode :: Decoder s TxStripped
$cdecode :: forall s. Decoder s TxStripped
encode :: TxStripped -> Encoding
$cencode :: TxStripped -> Encoding
Serialise)
strip :: Tx -> TxStripped
strip :: Tx -> TxStripped
strip Tx{[TxOut]
[Certificate]
[Withdrawal]
[TxInput]
Maybe Value
Maybe BuiltinByteString
Maybe TxOut
ScriptsMap
Map DatumHash Datum
MintingWitnessesMap
Map PubKey Signature
Value
SlotRange
txMetadata :: Maybe BuiltinByteString
txData :: Map DatumHash Datum
txScripts :: ScriptsMap
txSignatures :: Map PubKey Signature
txCertificates :: [Certificate]
txWithdrawals :: [Withdrawal]
txMintingWitnesses :: MintingWitnessesMap
txValidRange :: SlotRange
txFee :: Value
txMint :: Value
txTotalCollateral :: Maybe Value
txReturnCollateral :: Maybe TxOut
txOutputs :: [TxOut]
txCollateralInputs :: [TxInput]
txReferenceInputs :: [TxInput]
txInputs :: [TxInput]
txMetadata :: Tx -> Maybe BuiltinByteString
txData :: Tx -> Map DatumHash Datum
txScripts :: Tx -> ScriptsMap
txSignatures :: Tx -> Map PubKey Signature
txCertificates :: Tx -> [Certificate]
txWithdrawals :: Tx -> [Withdrawal]
txMintingWitnesses :: Tx -> MintingWitnessesMap
txValidRange :: Tx -> SlotRange
txFee :: Tx -> Value
txMint :: Tx -> Value
txTotalCollateral :: Tx -> Maybe Value
txReturnCollateral :: Tx -> Maybe TxOut
txOutputs :: Tx -> [TxOut]
txCollateralInputs :: Tx -> [TxInput]
txReferenceInputs :: Tx -> [TxInput]
txInputs :: Tx -> [TxInput]
..} = [TxOutRef] -> [TxOutRef] -> [TxOut] -> Value -> Value -> TxStripped
TxStripped [TxOutRef]
i [TxOutRef]
ri [TxOut]
txOutputs Value
txMint Value
txFee where
i :: [TxOutRef]
i = (TxInput -> TxOutRef) -> [TxInput] -> [TxOutRef]
forall a b. (a -> b) -> [a] -> [b]
map TxInput -> TxOutRef
txInputRef [TxInput]
txInputs
ri :: [TxOutRef]
ri = (TxInput -> TxOutRef) -> [TxInput] -> [TxOutRef]
forall a b. (a -> b) -> [a] -> [b]
map TxInput -> TxOutRef
txInputRef [TxInput]
txReferenceInputs
data TxOutTx = TxOutTx { TxOutTx -> Tx
txOutTxTx :: Tx, TxOutTx -> TxOut
txOutTxOut :: TxOut }
deriving stock (Int -> TxOutTx -> ShowS
[TxOutTx] -> ShowS
TxOutTx -> String
(Int -> TxOutTx -> ShowS)
-> (TxOutTx -> String) -> ([TxOutTx] -> ShowS) -> Show TxOutTx
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxOutTx] -> ShowS
$cshowList :: [TxOutTx] -> ShowS
show :: TxOutTx -> String
$cshow :: TxOutTx -> String
showsPrec :: Int -> TxOutTx -> ShowS
$cshowsPrec :: Int -> TxOutTx -> ShowS
Show, TxOutTx -> TxOutTx -> Bool
(TxOutTx -> TxOutTx -> Bool)
-> (TxOutTx -> TxOutTx -> Bool) -> Eq TxOutTx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxOutTx -> TxOutTx -> Bool
$c/= :: TxOutTx -> TxOutTx -> Bool
== :: TxOutTx -> TxOutTx -> Bool
$c== :: TxOutTx -> TxOutTx -> Bool
Eq, (forall x. TxOutTx -> Rep TxOutTx x)
-> (forall x. Rep TxOutTx x -> TxOutTx) -> Generic TxOutTx
forall x. Rep TxOutTx x -> TxOutTx
forall x. TxOutTx -> Rep TxOutTx x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxOutTx x -> TxOutTx
$cfrom :: forall x. TxOutTx -> Rep TxOutTx x
Generic)
deriving anyclass ([TxOutTx] -> Encoding
TxOutTx -> Encoding
(TxOutTx -> Encoding)
-> (forall s. Decoder s TxOutTx)
-> ([TxOutTx] -> Encoding)
-> (forall s. Decoder s [TxOutTx])
-> Serialise TxOutTx
forall s. Decoder s [TxOutTx]
forall s. Decoder s TxOutTx
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
decodeList :: Decoder s [TxOutTx]
$cdecodeList :: forall s. Decoder s [TxOutTx]
encodeList :: [TxOutTx] -> Encoding
$cencodeList :: [TxOutTx] -> Encoding
decode :: Decoder s TxOutTx
$cdecode :: forall s. Decoder s TxOutTx
encode :: TxOutTx -> Encoding
$cencode :: TxOutTx -> Encoding
Serialise, [TxOutTx] -> Encoding
[TxOutTx] -> Value
TxOutTx -> Encoding
TxOutTx -> Value
(TxOutTx -> Value)
-> (TxOutTx -> Encoding)
-> ([TxOutTx] -> Value)
-> ([TxOutTx] -> Encoding)
-> ToJSON TxOutTx
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TxOutTx] -> Encoding
$ctoEncodingList :: [TxOutTx] -> Encoding
toJSONList :: [TxOutTx] -> Value
$ctoJSONList :: [TxOutTx] -> Value
toEncoding :: TxOutTx -> Encoding
$ctoEncoding :: TxOutTx -> Encoding
toJSON :: TxOutTx -> Value
$ctoJSON :: TxOutTx -> Value
ToJSON, Value -> Parser [TxOutTx]
Value -> Parser TxOutTx
(Value -> Parser TxOutTx)
-> (Value -> Parser [TxOutTx]) -> FromJSON TxOutTx
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TxOutTx]
$cparseJSONList :: Value -> Parser [TxOutTx]
parseJSON :: Value -> Parser TxOutTx
$cparseJSON :: Value -> Parser TxOutTx
FromJSON)
txOutTxDatum :: TxOutTx -> Maybe Datum
txOutTxDatum :: TxOutTx -> Maybe Datum
txOutTxDatum (TxOutTx Tx
tx (TxOut (C.TxOut AddressInEra BabbageEra
_aie TxOutValue BabbageEra
_tov TxOutDatum CtxTx BabbageEra
tod ReferenceScript BabbageEra
_rs))) =
case TxOutDatum CtxTx BabbageEra
tod of
TxOutDatum CtxTx BabbageEra
C.TxOutDatumNone ->
Maybe Datum
forall a. Maybe a
Nothing
C.TxOutDatumHash ScriptDataSupportedInEra BabbageEra
_era Hash ScriptData
scriptDataHash ->
Tx -> DatumHash -> Maybe Datum
lookupDatum Tx
tx (DatumHash -> Maybe Datum) -> DatumHash -> Maybe Datum
forall a b. (a -> b) -> a -> b
$ BuiltinByteString -> DatumHash
DatumHash (BuiltinByteString -> DatumHash) -> BuiltinByteString -> DatumHash
forall a b. (a -> b) -> a -> b
$ ByteString -> BuiltinByteString
forall a arep. ToBuiltin a arep => a -> arep
PlutusTx.toBuiltin (Hash ScriptData -> ByteString
forall a. SerialiseAsRawBytes a => a -> ByteString
C.serialiseToRawBytes Hash ScriptData
scriptDataHash)
C.TxOutDatumInline ReferenceTxInsScriptsInlineDatumsSupportedInEra BabbageEra
_era ScriptData
scriptData ->
Datum -> Maybe Datum
forall a. a -> Maybe a
Just (Datum -> Maybe Datum) -> Datum -> Maybe Datum
forall a b. (a -> b) -> a -> b
$ BuiltinData -> Datum
Datum (BuiltinData -> Datum) -> BuiltinData -> Datum
forall a b. (a -> b) -> a -> b
$ Data -> BuiltinData
dataToBuiltinData (Data -> BuiltinData) -> Data -> BuiltinData
forall a b. (a -> b) -> a -> b
$ ScriptData -> Data
C.toPlutusData ScriptData
scriptData
C.TxOutDatumInTx ScriptDataSupportedInEra BabbageEra
_era ScriptData
scriptData ->
Datum -> Maybe Datum
forall a. a -> Maybe a
Just (Datum -> Maybe Datum) -> Datum -> Maybe Datum
forall a b. (a -> b) -> a -> b
$ BuiltinData -> Datum
Datum (BuiltinData -> Datum) -> BuiltinData -> Datum
forall a b. (a -> b) -> a -> b
$ Data -> BuiltinData
dataToBuiltinData (Data -> BuiltinData) -> Data -> BuiltinData
forall a b. (a -> b) -> a -> b
$ ScriptData -> Data
C.toPlutusData ScriptData
scriptData
txOutDatumHash :: TxOut -> Maybe DatumHash
txOutDatumHash :: TxOut -> Maybe DatumHash
txOutDatumHash (TxOut (C.TxOut AddressInEra BabbageEra
_aie TxOutValue BabbageEra
_tov TxOutDatum CtxTx BabbageEra
tod ReferenceScript BabbageEra
_rs)) =
case TxOutDatum CtxTx BabbageEra
tod of
TxOutDatum CtxTx BabbageEra
C.TxOutDatumNone ->
Maybe DatumHash
forall a. Maybe a
Nothing
C.TxOutDatumHash ScriptDataSupportedInEra BabbageEra
_era Hash ScriptData
scriptDataHash ->
DatumHash -> Maybe DatumHash
forall a. a -> Maybe a
Just (DatumHash -> Maybe DatumHash) -> DatumHash -> Maybe DatumHash
forall a b. (a -> b) -> a -> b
$ BuiltinByteString -> DatumHash
DatumHash (BuiltinByteString -> DatumHash) -> BuiltinByteString -> DatumHash
forall a b. (a -> b) -> a -> b
$ ByteString -> BuiltinByteString
forall a arep. ToBuiltin a arep => a -> arep
PlutusTx.toBuiltin (Hash ScriptData -> ByteString
forall a. SerialiseAsRawBytes a => a -> ByteString
C.serialiseToRawBytes Hash ScriptData
scriptDataHash)
C.TxOutDatumInline ReferenceTxInsScriptsInlineDatumsSupportedInEra BabbageEra
_era ScriptData
scriptData ->
DatumHash -> Maybe DatumHash
forall a. a -> Maybe a
Just (DatumHash -> Maybe DatumHash) -> DatumHash -> Maybe DatumHash
forall a b. (a -> b) -> a -> b
$ Datum -> DatumHash
datumHash (Datum -> DatumHash) -> Datum -> DatumHash
forall a b. (a -> b) -> a -> b
$ BuiltinData -> Datum
Datum (BuiltinData -> Datum) -> BuiltinData -> Datum
forall a b. (a -> b) -> a -> b
$ Data -> BuiltinData
dataToBuiltinData (Data -> BuiltinData) -> Data -> BuiltinData
forall a b. (a -> b) -> a -> b
$ ScriptData -> Data
C.toPlutusData ScriptData
scriptData
C.TxOutDatumInTx ScriptDataSupportedInEra BabbageEra
_era ScriptData
scriptData ->
DatumHash -> Maybe DatumHash
forall a. a -> Maybe a
Just (DatumHash -> Maybe DatumHash) -> DatumHash -> Maybe DatumHash
forall a b. (a -> b) -> a -> b
$ Datum -> DatumHash
datumHash (Datum -> DatumHash) -> Datum -> DatumHash
forall a b. (a -> b) -> a -> b
$ BuiltinData -> Datum
Datum (BuiltinData -> Datum) -> BuiltinData -> Datum
forall a b. (a -> b) -> a -> b
$ Data -> BuiltinData
dataToBuiltinData (Data -> BuiltinData) -> Data -> BuiltinData
forall a b. (a -> b) -> a -> b
$ ScriptData -> Data
C.toPlutusData ScriptData
scriptData
txOutPubKey :: TxOut -> Maybe PubKeyHash
txOutPubKey :: TxOut -> Maybe PubKeyHash
txOutPubKey (TxOut (C.TxOut AddressInEra BabbageEra
aie TxOutValue BabbageEra
_ TxOutDatum CtxTx BabbageEra
_ ReferenceScript BabbageEra
_)) = AddressInEra BabbageEra -> Maybe PubKeyHash
forall era. AddressInEra era -> Maybe PubKeyHash
cardanoPubKeyHash AddressInEra BabbageEra
aie
txOutAddress :: TxOut -> CardanoAddress
txOutAddress :: TxOut -> AddressInEra BabbageEra
txOutAddress (TxOut (C.TxOut AddressInEra BabbageEra
aie TxOutValue BabbageEra
_tov TxOutDatum CtxTx BabbageEra
_tod ReferenceScript BabbageEra
_rs)) = AddressInEra BabbageEra
aie
outAddress :: L.Lens' TxOut (C.AddressInEra C.BabbageEra)
outAddress :: (AddressInEra BabbageEra -> f (AddressInEra BabbageEra))
-> TxOut -> f TxOut
outAddress = (TxOut -> AddressInEra BabbageEra)
-> (TxOut -> AddressInEra BabbageEra -> TxOut)
-> Lens
TxOut TxOut (AddressInEra BabbageEra) (AddressInEra BabbageEra)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens
TxOut -> AddressInEra BabbageEra
txOutAddress
(\(TxOut (C.TxOut AddressInEra BabbageEra
_ TxOutValue BabbageEra
tov TxOutDatum CtxTx BabbageEra
tod ReferenceScript BabbageEra
rs)) AddressInEra BabbageEra
aie -> TxOut CtxTx BabbageEra -> TxOut
TxOut (AddressInEra BabbageEra
-> TxOutValue BabbageEra
-> TxOutDatum CtxTx BabbageEra
-> ReferenceScript BabbageEra
-> TxOut CtxTx BabbageEra
forall ctx era.
AddressInEra era
-> TxOutValue era
-> TxOutDatum ctx era
-> ReferenceScript era
-> TxOut ctx era
C.TxOut AddressInEra BabbageEra
aie TxOutValue BabbageEra
tov TxOutDatum CtxTx BabbageEra
tod ReferenceScript BabbageEra
rs))
outDatumHash :: L.Lens TxOut TxOut (Maybe DatumHash) (C.TxOutDatum C.CtxTx C.BabbageEra)
outDatumHash :: (Maybe DatumHash -> f (TxOutDatum CtxTx BabbageEra))
-> TxOut -> f TxOut
outDatumHash = (TxOut -> Maybe DatumHash)
-> (TxOut -> TxOutDatum CtxTx BabbageEra -> TxOut)
-> Lens TxOut TxOut (Maybe DatumHash) (TxOutDatum CtxTx BabbageEra)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens
TxOut -> Maybe DatumHash
txOutDatumHash
(\(TxOut (C.TxOut AddressInEra BabbageEra
aie TxOutValue BabbageEra
tov TxOutDatum CtxTx BabbageEra
_ ReferenceScript BabbageEra
rs)) TxOutDatum CtxTx BabbageEra
tod -> TxOut CtxTx BabbageEra -> TxOut
TxOut (AddressInEra BabbageEra
-> TxOutValue BabbageEra
-> TxOutDatum CtxTx BabbageEra
-> ReferenceScript BabbageEra
-> TxOut CtxTx BabbageEra
forall ctx era.
AddressInEra era
-> TxOutValue era
-> TxOutDatum ctx era
-> ReferenceScript era
-> TxOut ctx era
C.TxOut AddressInEra BabbageEra
aie TxOutValue BabbageEra
tov TxOutDatum CtxTx BabbageEra
tod ReferenceScript BabbageEra
rs))
type ReferenceScript = C.ReferenceScript C.BabbageEra
txOutReferenceScript :: TxOut -> ReferenceScript
txOutReferenceScript :: TxOut -> ReferenceScript BabbageEra
txOutReferenceScript (TxOut (C.TxOut AddressInEra BabbageEra
_aie TxOutValue BabbageEra
_tov TxOutDatum CtxTx BabbageEra
_tod ReferenceScript BabbageEra
rs)) = ReferenceScript BabbageEra
rs
outReferenceScript :: L.Lens' TxOut ReferenceScript
outReferenceScript :: (ReferenceScript BabbageEra -> f (ReferenceScript BabbageEra))
-> TxOut -> f TxOut
outReferenceScript = (TxOut -> ReferenceScript BabbageEra)
-> (TxOut -> ReferenceScript BabbageEra -> TxOut)
-> Lens
TxOut
TxOut
(ReferenceScript BabbageEra)
(ReferenceScript BabbageEra)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
L.lens
TxOut -> ReferenceScript BabbageEra
txOutReferenceScript
(\(TxOut (C.TxOut AddressInEra BabbageEra
aie TxOutValue BabbageEra
tov TxOutDatum CtxTx BabbageEra
tod ReferenceScript BabbageEra
_)) ReferenceScript BabbageEra
rs -> TxOut CtxTx BabbageEra -> TxOut
TxOut (AddressInEra BabbageEra
-> TxOutValue BabbageEra
-> TxOutDatum CtxTx BabbageEra
-> ReferenceScript BabbageEra
-> TxOut CtxTx BabbageEra
forall ctx era.
AddressInEra era
-> TxOutValue era
-> TxOutDatum ctx era
-> ReferenceScript era
-> TxOut ctx era
C.TxOut AddressInEra BabbageEra
aie TxOutValue BabbageEra
tov TxOutDatum CtxTx BabbageEra
tod ReferenceScript BabbageEra
rs))
lookupScript :: ScriptsMap -> ScriptHash -> Maybe (Versioned Script)
lookupScript :: ScriptsMap -> ScriptHash -> Maybe (Versioned Script)
lookupScript ScriptsMap
txScripts ScriptHash
hash = ScriptHash -> ScriptsMap -> Maybe (Versioned Script)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup ScriptHash
hash ScriptsMap
txScripts
lookupValidator :: ScriptsMap -> ValidatorHash -> Maybe (Versioned Validator)
lookupValidator :: ScriptsMap -> ValidatorHash -> Maybe (Versioned Validator)
lookupValidator ScriptsMap
txScripts = ((Versioned Script -> Versioned Validator)
-> Maybe (Versioned Script) -> Maybe (Versioned Validator)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Versioned Script -> Versioned Validator)
-> Maybe (Versioned Script) -> Maybe (Versioned Validator))
-> ((Script -> Validator)
-> Versioned Script -> Versioned Validator)
-> (Script -> Validator)
-> Maybe (Versioned Script)
-> Maybe (Versioned Validator)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Script -> Validator) -> Versioned Script -> Versioned Validator
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) Script -> Validator
Validator (Maybe (Versioned Script) -> Maybe (Versioned Validator))
-> (ValidatorHash -> Maybe (Versioned Script))
-> ValidatorHash
-> Maybe (Versioned Validator)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptsMap -> ScriptHash -> Maybe (Versioned Script)
lookupScript ScriptsMap
txScripts (ScriptHash -> Maybe (Versioned Script))
-> (ValidatorHash -> ScriptHash)
-> ValidatorHash
-> Maybe (Versioned Script)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValidatorHash -> ScriptHash
toScriptHash
where
toScriptHash :: ValidatorHash -> ScriptHash
toScriptHash (ValidatorHash BuiltinByteString
b) = BuiltinByteString -> ScriptHash
ScriptHash BuiltinByteString
b
spentOutputs :: Tx -> [TxOutRef]
spentOutputs :: Tx -> [TxOutRef]
spentOutputs = (TxInput -> TxOutRef) -> [TxInput] -> [TxOutRef]
forall a b. (a -> b) -> [a] -> [b]
map TxInput -> TxOutRef
txInputRef ([TxInput] -> [TxOutRef]) -> (Tx -> [TxInput]) -> Tx -> [TxOutRef]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tx -> [TxInput]
txInputs
referencedOutputs :: Tx -> [TxOutRef]
referencedOutputs :: Tx -> [TxOutRef]
referencedOutputs = (TxInput -> TxOutRef) -> [TxInput] -> [TxOutRef]
forall a b. (a -> b) -> [a] -> [b]
map TxInput -> TxOutRef
txInputRef ([TxInput] -> [TxOutRef]) -> (Tx -> [TxInput]) -> Tx -> [TxOutRef]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tx -> [TxInput]
txReferenceInputs
lookupMintingPolicy :: ScriptsMap -> MintingPolicyHash -> Maybe (Versioned MintingPolicy)
lookupMintingPolicy :: ScriptsMap -> MintingPolicyHash -> Maybe (Versioned MintingPolicy)
lookupMintingPolicy ScriptsMap
txScripts = ((Versioned Script -> Versioned MintingPolicy)
-> Maybe (Versioned Script) -> Maybe (Versioned MintingPolicy)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Versioned Script -> Versioned MintingPolicy)
-> Maybe (Versioned Script) -> Maybe (Versioned MintingPolicy))
-> ((Script -> MintingPolicy)
-> Versioned Script -> Versioned MintingPolicy)
-> (Script -> MintingPolicy)
-> Maybe (Versioned Script)
-> Maybe (Versioned MintingPolicy)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Script -> MintingPolicy)
-> Versioned Script -> Versioned MintingPolicy
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) Script -> MintingPolicy
MintingPolicy (Maybe (Versioned Script) -> Maybe (Versioned MintingPolicy))
-> (MintingPolicyHash -> Maybe (Versioned Script))
-> MintingPolicyHash
-> Maybe (Versioned MintingPolicy)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptsMap -> ScriptHash -> Maybe (Versioned Script)
lookupScript ScriptsMap
txScripts (ScriptHash -> Maybe (Versioned Script))
-> (MintingPolicyHash -> ScriptHash)
-> MintingPolicyHash
-> Maybe (Versioned Script)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MintingPolicyHash -> ScriptHash
toScriptHash
where
toScriptHash :: MintingPolicyHash -> ScriptHash
toScriptHash (MintingPolicyHash BuiltinByteString
b) = BuiltinByteString -> ScriptHash
ScriptHash BuiltinByteString
b
deriving instance OpenApi.ToSchema Tx
deriving instance OpenApi.ToSchema TxInputType
deriving instance OpenApi.ToSchema TxInput
deriving instance OpenApi.ToSchema Withdrawal
deriving instance OpenApi.ToSchema Certificate
lookupStakeValidator :: ScriptsMap -> StakeValidatorHash -> Maybe (Versioned StakeValidator)
lookupStakeValidator :: ScriptsMap
-> StakeValidatorHash -> Maybe (Versioned StakeValidator)
lookupStakeValidator ScriptsMap
txScripts = ((Versioned Script -> Versioned StakeValidator)
-> Maybe (Versioned Script) -> Maybe (Versioned StakeValidator)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Versioned Script -> Versioned StakeValidator)
-> Maybe (Versioned Script) -> Maybe (Versioned StakeValidator))
-> ((Script -> StakeValidator)
-> Versioned Script -> Versioned StakeValidator)
-> (Script -> StakeValidator)
-> Maybe (Versioned Script)
-> Maybe (Versioned StakeValidator)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Script -> StakeValidator)
-> Versioned Script -> Versioned StakeValidator
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) Script -> StakeValidator
StakeValidator (Maybe (Versioned Script) -> Maybe (Versioned StakeValidator))
-> (StakeValidatorHash -> Maybe (Versioned Script))
-> StakeValidatorHash
-> Maybe (Versioned StakeValidator)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptsMap -> ScriptHash -> Maybe (Versioned Script)
lookupScript ScriptsMap
txScripts (ScriptHash -> Maybe (Versioned Script))
-> (StakeValidatorHash -> ScriptHash)
-> StakeValidatorHash
-> Maybe (Versioned Script)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StakeValidatorHash -> ScriptHash
toScriptHash
where
toScriptHash :: StakeValidatorHash -> ScriptHash
toScriptHash (StakeValidatorHash BuiltinByteString
b) = BuiltinByteString -> ScriptHash
ScriptHash BuiltinByteString
b
fillTxInputWitnesses :: Tx -> TxInput -> TxIn
fillTxInputWitnesses :: Tx -> TxInput -> TxIn
fillTxInputWitnesses Tx
tx (TxInput TxOutRef
outRef TxInputType
_inType) = case TxInputType
_inType of
TxInputType
TxConsumePublicKeyAddress -> TxOutRef -> Maybe TxInType -> TxIn
TxIn TxOutRef
outRef (TxInType -> Maybe TxInType
forall a. a -> Maybe a
Just TxInType
ConsumePublicKeyAddress)
TxInputType
TxConsumeSimpleScriptAddress -> TxOutRef -> Maybe TxInType -> TxIn
TxIn TxOutRef
outRef (TxInType -> Maybe TxInType
forall a. a -> Maybe a
Just TxInType
ConsumeSimpleScriptAddress)
TxScriptAddress Redeemer
redeemer (Left ValidatorHash
vlh) Maybe DatumHash
dh -> TxOutRef -> Maybe TxInType -> TxIn
TxIn TxOutRef
outRef (Maybe TxInType -> TxIn) -> Maybe TxInType -> TxIn
forall a b. (a -> b) -> a -> b
$ do
Maybe Datum
datum <- (DatumHash -> Maybe Datum)
-> Maybe DatumHash -> Maybe (Maybe Datum)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (DatumHash -> Map DatumHash Datum -> Maybe Datum
forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Tx -> Map DatumHash Datum
txData Tx
tx) Maybe DatumHash
dh
Versioned Validator
validator <- ScriptsMap -> ValidatorHash -> Maybe (Versioned Validator)
lookupValidator (Tx -> ScriptsMap
txScripts Tx
tx) ValidatorHash
vlh
TxInType -> Maybe TxInType
forall a. a -> Maybe a
Just (TxInType -> Maybe TxInType) -> TxInType -> Maybe TxInType
forall a b. (a -> b) -> a -> b
$ Either (Versioned Validator) (Versioned TxOutRef)
-> Redeemer -> Maybe Datum -> TxInType
ScriptAddress (Versioned Validator
-> Either (Versioned Validator) (Versioned TxOutRef)
forall a b. a -> Either a b
Left Versioned Validator
validator) Redeemer
redeemer Maybe Datum
datum
TxScriptAddress Redeemer
redeemer (Right Versioned TxOutRef
ref) Maybe DatumHash
dh -> TxOutRef -> Maybe TxInType -> TxIn
TxIn TxOutRef
outRef (Maybe TxInType -> TxIn) -> Maybe TxInType -> TxIn
forall a b. (a -> b) -> a -> b
$ do
Maybe Datum
datum <- (DatumHash -> Maybe Datum)
-> Maybe DatumHash -> Maybe (Maybe Datum)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (DatumHash -> Map DatumHash Datum -> Maybe Datum
forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Tx -> Map DatumHash Datum
txData Tx
tx) Maybe DatumHash
dh
TxInType -> Maybe TxInType
forall a. a -> Maybe a
Just (TxInType -> Maybe TxInType) -> TxInType -> Maybe TxInType
forall a b. (a -> b) -> a -> b
$ Either (Versioned Validator) (Versioned TxOutRef)
-> Redeemer -> Maybe Datum -> TxInType
ScriptAddress (Versioned TxOutRef
-> Either (Versioned Validator) (Versioned TxOutRef)
forall a b. b -> Either a b
Right Versioned TxOutRef
ref) Redeemer
redeemer Maybe Datum
datum
pubKeyTxInput :: TxOutRef -> TxInput
pubKeyTxInput :: TxOutRef -> TxInput
pubKeyTxInput TxOutRef
outRef = TxOutRef -> TxInputType -> TxInput
TxInput TxOutRef
outRef TxInputType
TxConsumePublicKeyAddress
addMintingPolicy :: Versioned MintingPolicy -> (Redeemer, Maybe (Versioned TxOutRef)) -> Tx -> Tx
addMintingPolicy :: Versioned MintingPolicy
-> (Redeemer, Maybe (Versioned TxOutRef)) -> Tx -> Tx
addMintingPolicy Versioned MintingPolicy
vvl (Redeemer, Maybe (Versioned TxOutRef))
rdWithRef tx :: Tx
tx@Tx{MintingWitnessesMap
txMintingWitnesses :: MintingWitnessesMap
txMintingWitnesses :: Tx -> MintingWitnessesMap
txMintingWitnesses, ScriptsMap
txScripts :: ScriptsMap
txScripts :: Tx -> ScriptsMap
txScripts} = Tx
tx
{txMintingWitnesses :: MintingWitnessesMap
txMintingWitnesses = MintingPolicyHash
-> (Redeemer, Maybe (Versioned TxOutRef))
-> MintingWitnessesMap
-> MintingWitnessesMap
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert MintingPolicyHash
mph (Redeemer, Maybe (Versioned TxOutRef))
rdWithRef MintingWitnessesMap
txMintingWitnesses,
txScripts :: ScriptsMap
txScripts = ScriptHash -> Versioned Script -> ScriptsMap -> ScriptsMap
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (BuiltinByteString -> ScriptHash
ScriptHash BuiltinByteString
b) ((MintingPolicy -> Script)
-> Versioned MintingPolicy -> Versioned Script
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MintingPolicy -> Script
getMintingPolicy Versioned MintingPolicy
vvl) ScriptsMap
txScripts}
where
mph :: MintingPolicyHash
mph@(MintingPolicyHash BuiltinByteString
b) = Versioned MintingPolicy -> MintingPolicyHash
mintingPolicyHash Versioned MintingPolicy
vvl
addScriptTxInput :: TxOutRef -> Versioned Validator -> Redeemer -> Maybe Datum -> Tx -> Tx
addScriptTxInput :: TxOutRef
-> Versioned Validator -> Redeemer -> Maybe Datum -> Tx -> Tx
addScriptTxInput TxOutRef
outRef Versioned Validator
vl Redeemer
rd Maybe Datum
mdt tx :: Tx
tx@Tx{[TxInput]
txInputs :: [TxInput]
txInputs :: Tx -> [TxInput]
txInputs, ScriptsMap
txScripts :: ScriptsMap
txScripts :: Tx -> ScriptsMap
txScripts, Map DatumHash Datum
txData :: Map DatumHash Datum
txData :: Tx -> Map DatumHash Datum
txData} = Tx
tx
{txInputs :: [TxInput]
txInputs = TxOutRef -> TxInputType -> TxInput
TxInput TxOutRef
outRef (Redeemer
-> Either ValidatorHash (Versioned TxOutRef)
-> Maybe DatumHash
-> TxInputType
TxScriptAddress Redeemer
rd (ValidatorHash -> Either ValidatorHash (Versioned TxOutRef)
forall a b. a -> Either a b
Left ValidatorHash
vlHash) Maybe DatumHash
mdtHash) TxInput -> [TxInput] -> [TxInput]
forall a. a -> [a] -> [a]
: [TxInput]
txInputs,
txScripts :: ScriptsMap
txScripts = ScriptHash -> Versioned Script -> ScriptsMap -> ScriptsMap
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (BuiltinByteString -> ScriptHash
ScriptHash BuiltinByteString
b) ((Validator -> Script) -> Versioned Validator -> Versioned Script
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Validator -> Script
getValidator Versioned Validator
vl) ScriptsMap
txScripts,
txData :: Map DatumHash Datum
txData = Map DatumHash Datum
-> (Datum -> Map DatumHash Datum)
-> Maybe Datum
-> Map DatumHash Datum
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Map DatumHash Datum
txData (\Datum
dt -> DatumHash -> Datum -> Map DatumHash Datum -> Map DatumHash Datum
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (Datum -> DatumHash
datumHash Datum
dt) Datum
dt Map DatumHash Datum
txData) Maybe Datum
mdt}
where
mdtHash :: Maybe DatumHash
mdtHash = (Datum -> DatumHash) -> Maybe Datum -> Maybe DatumHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Datum -> DatumHash
datumHash Maybe Datum
mdt
vlHash :: ValidatorHash
vlHash@(ValidatorHash BuiltinByteString
b) = Versioned Validator -> ValidatorHash
validatorHash Versioned Validator
vl
addReferenceTxInput :: TxOutRef -> Versioned TxOutRef -> Redeemer -> Maybe Datum -> Tx -> Tx
addReferenceTxInput :: TxOutRef
-> Versioned TxOutRef -> Redeemer -> Maybe Datum -> Tx -> Tx
addReferenceTxInput TxOutRef
outRef Versioned TxOutRef
vref Redeemer
rd Maybe Datum
mdt tx :: Tx
tx@Tx{[TxInput]
txInputs :: [TxInput]
txInputs :: Tx -> [TxInput]
txInputs, Map DatumHash Datum
txData :: Map DatumHash Datum
txData :: Tx -> Map DatumHash Datum
txData} = Tx
tx
{txInputs :: [TxInput]
txInputs = TxOutRef -> TxInputType -> TxInput
TxInput TxOutRef
outRef (Redeemer
-> Either ValidatorHash (Versioned TxOutRef)
-> Maybe DatumHash
-> TxInputType
TxScriptAddress Redeemer
rd (Versioned TxOutRef -> Either ValidatorHash (Versioned TxOutRef)
forall a b. b -> Either a b
Right Versioned TxOutRef
vref) Maybe DatumHash
mdtHash) TxInput -> [TxInput] -> [TxInput]
forall a. a -> [a] -> [a]
: [TxInput]
txInputs,
txData :: Map DatumHash Datum
txData = Map DatumHash Datum
-> (Datum -> Map DatumHash Datum)
-> Maybe Datum
-> Map DatumHash Datum
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Map DatumHash Datum
txData (\Datum
dt -> DatumHash -> Datum -> Map DatumHash Datum -> Map DatumHash Datum
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (Datum -> DatumHash
datumHash Datum
dt) Datum
dt Map DatumHash Datum
txData) Maybe Datum
mdt}
where
mdtHash :: Maybe DatumHash
mdtHash = (Datum -> DatumHash) -> Maybe Datum -> Maybe DatumHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Datum -> DatumHash
datumHash Maybe Datum
mdt
txRedeemers :: Tx -> Map ScriptPurpose Redeemer
txRedeemers :: Tx -> Map ScriptPurpose Redeemer
txRedeemers = ((TxOutRef -> ScriptPurpose)
-> Map TxOutRef Redeemer -> Map ScriptPurpose Redeemer
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys TxOutRef -> ScriptPurpose
Spending (Map TxOutRef Redeemer -> Map ScriptPurpose Redeemer)
-> (Tx -> Map TxOutRef Redeemer)
-> Tx
-> Map ScriptPurpose Redeemer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tx -> Map TxOutRef Redeemer
txSpendingRedeemers)
(Tx -> Map ScriptPurpose Redeemer)
-> (Tx -> Map ScriptPurpose Redeemer)
-> Tx
-> Map ScriptPurpose Redeemer
forall a. Semigroup a => a -> a -> a
<> ((MintingPolicyHash -> ScriptPurpose)
-> Map MintingPolicyHash Redeemer -> Map ScriptPurpose Redeemer
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys (CurrencySymbol -> ScriptPurpose
Minting (CurrencySymbol -> ScriptPurpose)
-> (MintingPolicyHash -> CurrencySymbol)
-> MintingPolicyHash
-> ScriptPurpose
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MintingPolicyHash -> CurrencySymbol
mpsSymbol) (Map MintingPolicyHash Redeemer -> Map ScriptPurpose Redeemer)
-> (Tx -> Map MintingPolicyHash Redeemer)
-> Tx
-> Map ScriptPurpose Redeemer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tx -> Map MintingPolicyHash Redeemer
txMintingRedeemers)
(Tx -> Map ScriptPurpose Redeemer)
-> (Tx -> Map ScriptPurpose Redeemer)
-> Tx
-> Map ScriptPurpose Redeemer
forall a. Semigroup a => a -> a -> a
<> ((Credential -> ScriptPurpose)
-> Map Credential Redeemer -> Map ScriptPurpose Redeemer
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys (StakingCredential -> ScriptPurpose
Rewarding (StakingCredential -> ScriptPurpose)
-> (Credential -> StakingCredential) -> Credential -> ScriptPurpose
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Credential -> StakingCredential
StakingHash) (Map Credential Redeemer -> Map ScriptPurpose Redeemer)
-> (Tx -> Map Credential Redeemer)
-> Tx
-> Map ScriptPurpose Redeemer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tx -> Map Credential Redeemer
txRewardingRedeemers)
(Tx -> Map ScriptPurpose Redeemer)
-> (Tx -> Map ScriptPurpose Redeemer)
-> Tx
-> Map ScriptPurpose Redeemer
forall a. Semigroup a => a -> a -> a
<> ((DCert -> ScriptPurpose)
-> Map DCert Redeemer -> Map ScriptPurpose Redeemer
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys DCert -> ScriptPurpose
Certifying (Map DCert Redeemer -> Map ScriptPurpose Redeemer)
-> (Tx -> Map DCert Redeemer) -> Tx -> Map ScriptPurpose Redeemer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tx -> Map DCert Redeemer
txCertifyingRedeemers)
txSpendingRedeemers :: Tx -> Map TxOutRef Redeemer
txSpendingRedeemers :: Tx -> Map TxOutRef Redeemer
txSpendingRedeemers Tx{[TxInput]
txInputs :: [TxInput]
txInputs :: Tx -> [TxInput]
txInputs} = (State (Map TxOutRef Redeemer) ()
-> Map TxOutRef Redeemer -> Map TxOutRef Redeemer)
-> Map TxOutRef Redeemer
-> State (Map TxOutRef Redeemer) ()
-> Map TxOutRef Redeemer
forall a b c. (a -> b -> c) -> b -> a -> c
flip State (Map TxOutRef Redeemer) ()
-> Map TxOutRef Redeemer -> Map TxOutRef Redeemer
forall s a. State s a -> s -> s
execState Map TxOutRef Redeemer
forall k a. Map k a
Map.empty (State (Map TxOutRef Redeemer) () -> Map TxOutRef Redeemer)
-> State (Map TxOutRef Redeemer) () -> Map TxOutRef Redeemer
forall a b. (a -> b) -> a -> b
$ (TxInput -> State (Map TxOutRef Redeemer) ())
-> [TxInput] -> State (Map TxOutRef Redeemer) ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ TxInput -> State (Map TxOutRef Redeemer) ()
forall (m :: * -> *).
MonadState (Map TxOutRef Redeemer) m =>
TxInput -> m ()
extract [TxInput]
txInputs where
extract :: TxInput -> m ()
extract TxInput{txInputType :: TxInput -> TxInputType
txInputType=TxScriptAddress Redeemer
redeemer Either ValidatorHash (Versioned TxOutRef)
_ Maybe DatumHash
_, TxOutRef
txInputRef :: TxOutRef
txInputRef :: TxInput -> TxOutRef
txInputRef} =
(Map TxOutRef Redeemer -> Map TxOutRef Redeemer) -> m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' ((Map TxOutRef Redeemer -> Map TxOutRef Redeemer) -> m ())
-> (Map TxOutRef Redeemer -> Map TxOutRef Redeemer) -> m ()
forall a b. (a -> b) -> a -> b
$ TxOutRef
-> Redeemer -> Map TxOutRef Redeemer -> Map TxOutRef Redeemer
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert TxOutRef
txInputRef Redeemer
redeemer
extract TxInput
_ = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
txMintingRedeemers :: Tx -> Map MintingPolicyHash Redeemer
txMintingRedeemers :: Tx -> Map MintingPolicyHash Redeemer
txMintingRedeemers Tx{MintingWitnessesMap
txMintingWitnesses :: MintingWitnessesMap
txMintingWitnesses :: Tx -> MintingWitnessesMap
txMintingWitnesses} = ((Redeemer, Maybe (Versioned TxOutRef)) -> Redeemer)
-> MintingWitnessesMap -> Map MintingPolicyHash Redeemer
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (Redeemer, Maybe (Versioned TxOutRef)) -> Redeemer
forall a b. (a, b) -> a
fst MintingWitnessesMap
txMintingWitnesses
txRewardingRedeemers :: Tx -> Map Credential Redeemer
txRewardingRedeemers :: Tx -> Map Credential Redeemer
txRewardingRedeemers Tx{[Withdrawal]
txWithdrawals :: [Withdrawal]
txWithdrawals :: Tx -> [Withdrawal]
txWithdrawals} = (State (Map Credential Redeemer) ()
-> Map Credential Redeemer -> Map Credential Redeemer)
-> Map Credential Redeemer
-> State (Map Credential Redeemer) ()
-> Map Credential Redeemer
forall a b c. (a -> b -> c) -> b -> a -> c
flip State (Map Credential Redeemer) ()
-> Map Credential Redeemer -> Map Credential Redeemer
forall s a. State s a -> s -> s
execState Map Credential Redeemer
forall k a. Map k a
Map.empty (State (Map Credential Redeemer) () -> Map Credential Redeemer)
-> State (Map Credential Redeemer) () -> Map Credential Redeemer
forall a b. (a -> b) -> a -> b
$ (Withdrawal -> State (Map Credential Redeemer) ())
-> [Withdrawal] -> State (Map Credential Redeemer) ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ Withdrawal -> State (Map Credential Redeemer) ()
forall (m :: * -> *).
MonadState (Map Credential Redeemer) m =>
Withdrawal -> m ()
f [Withdrawal]
txWithdrawals where
f :: Withdrawal -> m ()
f (Withdrawal Credential
cred Integer
_ (Just Redeemer
rd)) = (Map Credential Redeemer -> Map Credential Redeemer) -> m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' ((Map Credential Redeemer -> Map Credential Redeemer) -> m ())
-> (Map Credential Redeemer -> Map Credential Redeemer) -> m ()
forall a b. (a -> b) -> a -> b
$ Credential
-> Redeemer -> Map Credential Redeemer -> Map Credential Redeemer
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Credential
cred Redeemer
rd
f Withdrawal
_ = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
txCertifyingRedeemers :: Tx -> Map DCert Redeemer
txCertifyingRedeemers :: Tx -> Map DCert Redeemer
txCertifyingRedeemers Tx{[Certificate]
txCertificates :: [Certificate]
txCertificates :: Tx -> [Certificate]
txCertificates} = (State (Map DCert Redeemer) ()
-> Map DCert Redeemer -> Map DCert Redeemer)
-> Map DCert Redeemer
-> State (Map DCert Redeemer) ()
-> Map DCert Redeemer
forall a b c. (a -> b -> c) -> b -> a -> c
flip State (Map DCert Redeemer) ()
-> Map DCert Redeemer -> Map DCert Redeemer
forall s a. State s a -> s -> s
execState Map DCert Redeemer
forall k a. Map k a
Map.empty (State (Map DCert Redeemer) () -> Map DCert Redeemer)
-> State (Map DCert Redeemer) () -> Map DCert Redeemer
forall a b. (a -> b) -> a -> b
$ (Certificate -> State (Map DCert Redeemer) ())
-> [Certificate] -> State (Map DCert Redeemer) ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ Certificate -> State (Map DCert Redeemer) ()
forall (m :: * -> *).
MonadState (Map DCert Redeemer) m =>
Certificate -> m ()
f [Certificate]
txCertificates where
f :: Certificate -> m ()
f (Certificate DCert
dcert (Just Redeemer
rd)) = (Map DCert Redeemer -> Map DCert Redeemer) -> m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' ((Map DCert Redeemer -> Map DCert Redeemer) -> m ())
-> (Map DCert Redeemer -> Map DCert Redeemer) -> m ()
forall a b. (a -> b) -> a -> b
$ DCert -> Redeemer -> Map DCert Redeemer -> Map DCert Redeemer
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert DCert
dcert Redeemer
rd
f Certificate
_ = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()