module Cardano.Api.UTxO where
import Cardano.Api hiding (UTxO, toLedgerUTxO)
import Cardano.Api qualified
import Cardano.Api.Shelley (ReferenceScript (..))
import Cardano.Ledger.Babbage ()
import Data.Bifunctor (second)
import Data.Coerce (coerce)
import Data.Foldable qualified as F
import Data.List qualified as List
import Data.Map (Map)
import Data.Map qualified as Map
import Data.Set (Set)
import Data.Text (Text)
import Data.Text qualified as T
import Prelude
type Era = ConwayEra
type UTxO = UTxO' (TxOut CtxUTxO Era)
newtype UTxO' out = UTxO
{ forall out. UTxO' out -> Map TxIn out
toMap :: Map TxIn out
}
deriving newtype
( UTxO' out -> UTxO' out -> Bool
(UTxO' out -> UTxO' out -> Bool)
-> (UTxO' out -> UTxO' out -> Bool) -> Eq (UTxO' out)
forall out. Eq out => UTxO' out -> UTxO' out -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall out. Eq out => UTxO' out -> UTxO' out -> Bool
== :: UTxO' out -> UTxO' out -> Bool
$c/= :: forall out. Eq out => UTxO' out -> UTxO' out -> Bool
/= :: UTxO' out -> UTxO' out -> Bool
Eq
, Int -> UTxO' out -> ShowS
[UTxO' out] -> ShowS
UTxO' out -> String
(Int -> UTxO' out -> ShowS)
-> (UTxO' out -> String)
-> ([UTxO' out] -> ShowS)
-> Show (UTxO' out)
forall out. Show out => Int -> UTxO' out -> ShowS
forall out. Show out => [UTxO' out] -> ShowS
forall out. Show out => UTxO' out -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall out. Show out => Int -> UTxO' out -> ShowS
showsPrec :: Int -> UTxO' out -> ShowS
$cshow :: forall out. Show out => UTxO' out -> String
show :: UTxO' out -> String
$cshowList :: forall out. Show out => [UTxO' out] -> ShowS
showList :: [UTxO' out] -> ShowS
Show
, (forall a b. (a -> b) -> UTxO' a -> UTxO' b)
-> (forall a b. a -> UTxO' b -> UTxO' a) -> Functor UTxO'
forall a b. a -> UTxO' b -> UTxO' a
forall a b. (a -> b) -> UTxO' a -> UTxO' b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> UTxO' a -> UTxO' b
fmap :: forall a b. (a -> b) -> UTxO' a -> UTxO' b
$c<$ :: forall a b. a -> UTxO' b -> UTxO' a
<$ :: forall a b. a -> UTxO' b -> UTxO' a
Functor
, (forall m. Monoid m => UTxO' m -> m)
-> (forall m a. Monoid m => (a -> m) -> UTxO' a -> m)
-> (forall m a. Monoid m => (a -> m) -> UTxO' a -> m)
-> (forall a b. (a -> b -> b) -> b -> UTxO' a -> b)
-> (forall a b. (a -> b -> b) -> b -> UTxO' a -> b)
-> (forall b a. (b -> a -> b) -> b -> UTxO' a -> b)
-> (forall b a. (b -> a -> b) -> b -> UTxO' a -> b)
-> (forall a. (a -> a -> a) -> UTxO' a -> a)
-> (forall a. (a -> a -> a) -> UTxO' a -> a)
-> (forall a. UTxO' a -> [a])
-> (forall a. UTxO' a -> Bool)
-> (forall a. UTxO' a -> Int)
-> (forall a. Eq a => a -> UTxO' a -> Bool)
-> (forall a. Ord a => UTxO' a -> a)
-> (forall a. Ord a => UTxO' a -> a)
-> (forall a. Num a => UTxO' a -> a)
-> (forall a. Num a => UTxO' a -> a)
-> Foldable UTxO'
forall a. Eq a => a -> UTxO' a -> Bool
forall a. Num a => UTxO' a -> a
forall a. Ord a => UTxO' a -> a
forall m. Monoid m => UTxO' m -> m
forall a. UTxO' a -> Bool
forall a. UTxO' a -> Int
forall a. UTxO' a -> [a]
forall a. (a -> a -> a) -> UTxO' a -> a
forall m a. Monoid m => (a -> m) -> UTxO' a -> m
forall b a. (b -> a -> b) -> b -> UTxO' a -> b
forall a b. (a -> b -> b) -> b -> UTxO' a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => UTxO' m -> m
fold :: forall m. Monoid m => UTxO' m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> UTxO' a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> UTxO' a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> UTxO' a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> UTxO' a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> UTxO' a -> b
foldr :: forall a b. (a -> b -> b) -> b -> UTxO' a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> UTxO' a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> UTxO' a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> UTxO' a -> b
foldl :: forall b a. (b -> a -> b) -> b -> UTxO' a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> UTxO' a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> UTxO' a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> UTxO' a -> a
foldr1 :: forall a. (a -> a -> a) -> UTxO' a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> UTxO' a -> a
foldl1 :: forall a. (a -> a -> a) -> UTxO' a -> a
$ctoList :: forall a. UTxO' a -> [a]
toList :: forall a. UTxO' a -> [a]
$cnull :: forall a. UTxO' a -> Bool
null :: forall a. UTxO' a -> Bool
$clength :: forall a. UTxO' a -> Int
length :: forall a. UTxO' a -> Int
$celem :: forall a. Eq a => a -> UTxO' a -> Bool
elem :: forall a. Eq a => a -> UTxO' a -> Bool
$cmaximum :: forall a. Ord a => UTxO' a -> a
maximum :: forall a. Ord a => UTxO' a -> a
$cminimum :: forall a. Ord a => UTxO' a -> a
minimum :: forall a. Ord a => UTxO' a -> a
$csum :: forall a. Num a => UTxO' a -> a
sum :: forall a. Num a => UTxO' a -> a
$cproduct :: forall a. Num a => UTxO' a -> a
product :: forall a. Num a => UTxO' a -> a
Foldable
, NonEmpty (UTxO' out) -> UTxO' out
UTxO' out -> UTxO' out -> UTxO' out
(UTxO' out -> UTxO' out -> UTxO' out)
-> (NonEmpty (UTxO' out) -> UTxO' out)
-> (forall b. Integral b => b -> UTxO' out -> UTxO' out)
-> Semigroup (UTxO' out)
forall b. Integral b => b -> UTxO' out -> UTxO' out
forall out. NonEmpty (UTxO' out) -> UTxO' out
forall out. UTxO' out -> UTxO' out -> UTxO' out
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall out b. Integral b => b -> UTxO' out -> UTxO' out
$c<> :: forall out. UTxO' out -> UTxO' out -> UTxO' out
<> :: UTxO' out -> UTxO' out -> UTxO' out
$csconcat :: forall out. NonEmpty (UTxO' out) -> UTxO' out
sconcat :: NonEmpty (UTxO' out) -> UTxO' out
$cstimes :: forall out b. Integral b => b -> UTxO' out -> UTxO' out
stimes :: forall b. Integral b => b -> UTxO' out -> UTxO' out
Semigroup
, Semigroup (UTxO' out)
UTxO' out
Semigroup (UTxO' out) =>
UTxO' out
-> (UTxO' out -> UTxO' out -> UTxO' out)
-> ([UTxO' out] -> UTxO' out)
-> Monoid (UTxO' out)
[UTxO' out] -> UTxO' out
UTxO' out -> UTxO' out -> UTxO' out
forall out. Semigroup (UTxO' out)
forall out. UTxO' out
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall out. [UTxO' out] -> UTxO' out
forall out. UTxO' out -> UTxO' out -> UTxO' out
$cmempty :: forall out. UTxO' out
mempty :: UTxO' out
$cmappend :: forall out. UTxO' out -> UTxO' out -> UTxO' out
mappend :: UTxO' out -> UTxO' out -> UTxO' out
$cmconcat :: forall out. [UTxO' out] -> UTxO' out
mconcat :: [UTxO' out] -> UTxO' out
Monoid
, [UTxO' out] -> Value
[UTxO' out] -> Encoding
UTxO' out -> Bool
UTxO' out -> Value
UTxO' out -> Encoding
(UTxO' out -> Value)
-> (UTxO' out -> Encoding)
-> ([UTxO' out] -> Value)
-> ([UTxO' out] -> Encoding)
-> (UTxO' out -> Bool)
-> ToJSON (UTxO' out)
forall out. ToJSON out => [UTxO' out] -> Value
forall out. ToJSON out => [UTxO' out] -> Encoding
forall out. ToJSON out => UTxO' out -> Bool
forall out. ToJSON out => UTxO' out -> Value
forall out. ToJSON out => UTxO' out -> Encoding
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: forall out. ToJSON out => UTxO' out -> Value
toJSON :: UTxO' out -> Value
$ctoEncoding :: forall out. ToJSON out => UTxO' out -> Encoding
toEncoding :: UTxO' out -> Encoding
$ctoJSONList :: forall out. ToJSON out => [UTxO' out] -> Value
toJSONList :: [UTxO' out] -> Value
$ctoEncodingList :: forall out. ToJSON out => [UTxO' out] -> Encoding
toEncodingList :: [UTxO' out] -> Encoding
$comitField :: forall out. ToJSON out => UTxO' out -> Bool
omitField :: UTxO' out -> Bool
ToJSON
, Maybe (UTxO' out)
Value -> Parser [UTxO' out]
Value -> Parser (UTxO' out)
(Value -> Parser (UTxO' out))
-> (Value -> Parser [UTxO' out])
-> Maybe (UTxO' out)
-> FromJSON (UTxO' out)
forall out. FromJSON out => Maybe (UTxO' out)
forall out. FromJSON out => Value -> Parser [UTxO' out]
forall out. FromJSON out => Value -> Parser (UTxO' out)
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: forall out. FromJSON out => Value -> Parser (UTxO' out)
parseJSON :: Value -> Parser (UTxO' out)
$cparseJSONList :: forall out. FromJSON out => Value -> Parser [UTxO' out]
parseJSONList :: Value -> Parser [UTxO' out]
$comittedField :: forall out. FromJSON out => Maybe (UTxO' out)
omittedField :: Maybe (UTxO' out)
FromJSON
)
fromList :: [(TxIn, out)] -> UTxO' out
fromList :: forall out. [(TxIn, out)] -> UTxO' out
fromList = Map TxIn out -> UTxO' out
forall out. Map TxIn out -> UTxO' out
UTxO (Map TxIn out -> UTxO' out)
-> ([(TxIn, out)] -> Map TxIn out) -> [(TxIn, out)] -> UTxO' out
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(TxIn, out)] -> Map TxIn out
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
singleton :: TxIn -> out -> UTxO' out
singleton :: forall out. TxIn -> out -> UTxO' out
singleton TxIn
i out
o = Map TxIn out -> UTxO' out
forall out. Map TxIn out -> UTxO' out
UTxO (Map TxIn out -> UTxO' out) -> Map TxIn out -> UTxO' out
forall a b. (a -> b) -> a -> b
$ TxIn -> out -> Map TxIn out
forall k a. k -> a -> Map k a
Map.singleton TxIn
i out
o
resolveTxIn :: TxIn -> UTxO' out -> Maybe out
resolveTxIn :: forall out. TxIn -> UTxO' out -> Maybe out
resolveTxIn TxIn
k = TxIn -> Map TxIn out -> Maybe out
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup TxIn
k (Map TxIn out -> Maybe out)
-> (UTxO' out -> Map TxIn out) -> UTxO' out -> Maybe out
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTxO' out -> Map TxIn out
forall out. UTxO' out -> Map TxIn out
toMap
toList :: UTxO' out -> [(TxIn, out)]
toList :: forall out. UTxO' out -> [(TxIn, out)]
toList = Map TxIn out -> [(TxIn, out)]
forall k a. Map k a -> [(k, a)]
Map.toList (Map TxIn out -> [(TxIn, out)])
-> (UTxO' out -> Map TxIn out) -> UTxO' out -> [(TxIn, out)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTxO' out -> Map TxIn out
forall out. UTxO' out -> Map TxIn out
toMap
find :: (out -> Bool) -> UTxO' out -> Maybe (TxIn, out)
find :: forall out. (out -> Bool) -> UTxO' out -> Maybe (TxIn, out)
find out -> Bool
fn = ((TxIn, out) -> Bool) -> UTxO' out -> Maybe (TxIn, out)
forall out. ((TxIn, out) -> Bool) -> UTxO' out -> Maybe (TxIn, out)
findBy (out -> Bool
fn (out -> Bool) -> ((TxIn, out) -> out) -> (TxIn, out) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxIn, out) -> out
forall a b. (a, b) -> b
snd)
findBy :: ((TxIn, out) -> Bool) -> UTxO' out -> Maybe (TxIn, out)
findBy :: forall out. ((TxIn, out) -> Bool) -> UTxO' out -> Maybe (TxIn, out)
findBy (TxIn, out) -> Bool
fn UTxO' out
utxo = ((TxIn, out) -> Bool) -> [(TxIn, out)] -> Maybe (TxIn, out)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
List.find (TxIn, out) -> Bool
fn ([(TxIn, out)] -> Maybe (TxIn, out))
-> [(TxIn, out)] -> Maybe (TxIn, out)
forall a b. (a -> b) -> a -> b
$ UTxO' out -> [(TxIn, out)]
forall out. UTxO' out -> [(TxIn, out)]
toList UTxO' out
utxo
filter :: (out -> Bool) -> UTxO' out -> UTxO' out
filter :: forall out. (out -> Bool) -> UTxO' out -> UTxO' out
filter out -> Bool
fn = Map TxIn out -> UTxO' out
forall out. Map TxIn out -> UTxO' out
UTxO (Map TxIn out -> UTxO' out)
-> (UTxO' out -> Map TxIn out) -> UTxO' out -> UTxO' out
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (out -> Bool) -> Map TxIn out -> Map TxIn out
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter out -> Bool
fn (Map TxIn out -> Map TxIn out)
-> (UTxO' out -> Map TxIn out) -> UTxO' out -> Map TxIn out
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTxO' out -> Map TxIn out
forall out. UTxO' out -> Map TxIn out
toMap
inputSet :: UTxO' out -> Set TxIn
inputSet :: forall out. UTxO' out -> Set TxIn
inputSet = Map TxIn out -> Set TxIn
forall k a. Map k a -> Set k
Map.keysSet (Map TxIn out -> Set TxIn)
-> (UTxO' out -> Map TxIn out) -> UTxO' out -> Set TxIn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTxO' out -> Map TxIn out
forall out. UTxO' out -> Map TxIn out
toMap
render :: (TxIn, TxOut ctx era) -> Text
render :: forall ctx era. (TxIn, TxOut ctx era) -> Text
render (TxIn
k, TxOut AddressInEra era
_ (TxOutValue era -> Value
forall era. TxOutValue era -> Value
txOutValueToValue -> Value
v) TxOutDatum ctx era
_ ReferenceScript era
_) =
Int -> Text -> Text
T.drop Int
54 (TxIn -> Text
renderTxIn TxIn
k) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" ↦ " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Value -> Text
renderValue Value
v
difference :: UTxO' out -> UTxO' out -> UTxO' out
difference :: forall out. UTxO' out -> UTxO' out -> UTxO' out
difference UTxO' out
a UTxO' out
b = Map TxIn out -> UTxO' out
forall out. Map TxIn out -> UTxO' out
UTxO (Map TxIn out -> UTxO' out) -> Map TxIn out -> UTxO' out
forall a b. (a -> b) -> a -> b
$ Map TxIn out -> Map TxIn out -> Map TxIn out
forall k a b. Ord k => Map k a -> Map k b -> Map k a
Map.difference (UTxO' out -> Map TxIn out
forall out. UTxO' out -> Map TxIn out
toMap UTxO' out
a) (UTxO' out -> Map TxIn out
forall out. UTxO' out -> Map TxIn out
toMap UTxO' out
b)
containsOutputs :: Eq out => UTxO' out -> UTxO' out -> Bool
containsOutputs :: forall out. Eq out => UTxO' out -> UTxO' out -> Bool
containsOutputs UTxO' out
utxoForSearching UTxO' out
utxo =
let allOutputs :: [out]
allOutputs = UTxO' out -> [out]
forall a. UTxO' a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList UTxO' out
utxoForSearching
expectedOutputs :: [out]
expectedOutputs = UTxO' out -> [out]
forall a. UTxO' a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList UTxO' out
utxo
in (out -> Bool) -> [out] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (out -> [out] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [out]
allOutputs) [out]
expectedOutputs
fromApi :: Cardano.Api.UTxO era -> UTxO
fromApi :: forall era. UTxO era -> UTxO
fromApi (Cardano.Api.UTxO Map TxIn (TxOut CtxUTxO era)
eraUTxO) =
[(TxIn, TxOut CtxUTxO Era)] -> UTxO
forall out. [(TxIn, out)] -> UTxO' out
fromList ([(TxIn, TxOut CtxUTxO Era)] -> UTxO)
-> [(TxIn, TxOut CtxUTxO Era)] -> UTxO
forall a b. (a -> b) -> a -> b
$ (TxOut CtxUTxO era -> TxOut CtxUTxO Era)
-> (TxIn, TxOut CtxUTxO era) -> (TxIn, TxOut CtxUTxO Era)
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second TxOut CtxUTxO era -> TxOut CtxUTxO Era
forall era. TxOut CtxUTxO era -> TxOut CtxUTxO Era
convertOutputToEra ((TxIn, TxOut CtxUTxO era) -> (TxIn, TxOut CtxUTxO Era))
-> [(TxIn, TxOut CtxUTxO era)] -> [(TxIn, TxOut CtxUTxO Era)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map TxIn (TxOut CtxUTxO era) -> [(TxIn, TxOut CtxUTxO era)]
forall k a. Map k a -> [(k, a)]
Map.toList Map TxIn (TxOut CtxUTxO era)
eraUTxO
where
convertOutputToEra :: TxOut CtxUTxO era -> TxOut CtxUTxO Era
convertOutputToEra :: forall era. TxOut CtxUTxO era -> TxOut CtxUTxO Era
convertOutputToEra (TxOut AddressInEra era
eraAddress TxOutValue era
eraValue TxOutDatum CtxUTxO era
eraDatum ReferenceScript era
eraRefScript) =
AddressInEra Era
-> TxOutValue Era
-> TxOutDatum CtxUTxO Era
-> ReferenceScript Era
-> TxOut CtxUTxO Era
forall ctx era.
AddressInEra era
-> TxOutValue era
-> TxOutDatum ctx era
-> ReferenceScript era
-> TxOut ctx era
TxOut
(AddressInEra era -> AddressInEra Era
forall era. AddressInEra era -> AddressInEra Era
convertAddressToEra AddressInEra era
eraAddress)
(TxOutValue era -> TxOutValue Era
forall era. TxOutValue era -> TxOutValue Era
convertValueToEra TxOutValue era
eraValue)
(TxOutDatum CtxUTxO era -> TxOutDatum CtxUTxO Era
forall era. TxOutDatum CtxUTxO era -> TxOutDatum CtxUTxO Era
convertDatumToEra TxOutDatum CtxUTxO era
eraDatum)
(ReferenceScript era -> ReferenceScript Era
forall era. ReferenceScript era -> ReferenceScript Era
convertRefScriptToEra ReferenceScript era
eraRefScript)
convertAddressToEra :: AddressInEra era -> AddressInEra Era
convertAddressToEra :: forall era. AddressInEra era -> AddressInEra Era
convertAddressToEra (AddressInEra AddressTypeInEra addrtype era
_ Address addrtype
eraAddress) = ShelleyBasedEra Era -> AddressAny -> AddressInEra Era
forall era. ShelleyBasedEra era -> AddressAny -> AddressInEra era
anyAddressInShelleyBasedEra ShelleyBasedEra Era
forall era. IsShelleyBasedEra era => ShelleyBasedEra era
shelleyBasedEra (Address addrtype -> AddressAny
forall addr. Address addr -> AddressAny
toAddressAny Address addrtype
eraAddress)
convertValueToEra :: TxOutValue era -> TxOutValue Era
convertValueToEra :: forall era. TxOutValue era -> TxOutValue Era
convertValueToEra (TxOutValueByron Coin
lovelace) = ShelleyBasedEra Era -> Coin -> TxOutValue Era
forall era. ShelleyBasedEra era -> Coin -> TxOutValue era
lovelaceToTxOutValue ShelleyBasedEra Era
forall era. IsShelleyBasedEra era => ShelleyBasedEra era
shelleyBasedEra Coin
lovelace
convertValueToEra (TxOutValueShelleyBased ShelleyBasedEra era
sbe Value (ShelleyLedgerEra era)
value) = ShelleyBasedEra Era
-> Value (ShelleyLedgerEra Era) -> TxOutValue Era
forall era.
(Eq (Value (ShelleyLedgerEra era)),
Show (Value (ShelleyLedgerEra era))) =>
ShelleyBasedEra era
-> Value (ShelleyLedgerEra era) -> TxOutValue era
TxOutValueShelleyBased ShelleyBasedEra Era
forall era. IsShelleyBasedEra era => ShelleyBasedEra era
shelleyBasedEra (MaryEraOnwards Era -> Value -> Value (ShelleyLedgerEra Era)
forall era.
MaryEraOnwards era -> Value -> Value (ShelleyLedgerEra era)
toLedgerValue (forall era. IsMaryBasedEra era => MaryEraOnwards era
maryBasedEra @Era) (Value -> Value (ShelleyLedgerEra Era))
-> Value -> Value (ShelleyLedgerEra Era)
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era -> Value (ShelleyLedgerEra era) -> Value
forall era.
ShelleyBasedEra era -> Value (ShelleyLedgerEra era) -> Value
fromLedgerValue ShelleyBasedEra era
sbe Value (ShelleyLedgerEra era)
value)
convertDatumToEra :: TxOutDatum CtxUTxO era -> TxOutDatum CtxUTxO Era
convertDatumToEra :: forall era. TxOutDatum CtxUTxO era -> TxOutDatum CtxUTxO Era
convertDatumToEra TxOutDatum CtxUTxO era
TxOutDatumNone = TxOutDatum CtxUTxO Era
forall ctx era. TxOutDatum ctx era
TxOutDatumNone
convertDatumToEra (TxOutDatumHash AlonzoEraOnwards era
_ Hash ScriptData
hashScriptData) = AlonzoEraOnwards Era -> Hash ScriptData -> TxOutDatum CtxUTxO Era
forall era ctx.
AlonzoEraOnwards era -> Hash ScriptData -> TxOutDatum ctx era
TxOutDatumHash AlonzoEraOnwards Era
forall era. IsAlonzoBasedEra era => AlonzoEraOnwards era
alonzoBasedEra Hash ScriptData
hashScriptData
convertDatumToEra (TxOutDatumInline BabbageEraOnwards era
_ HashableScriptData
hashableScriptData) = BabbageEraOnwards Era
-> HashableScriptData -> TxOutDatum CtxUTxO Era
forall era ctx.
BabbageEraOnwards era -> HashableScriptData -> TxOutDatum ctx era
TxOutDatumInline BabbageEraOnwards Era
forall era. IsBabbageBasedEra era => BabbageEraOnwards era
babbageBasedEra HashableScriptData
hashableScriptData
convertRefScriptToEra :: ReferenceScript era -> ReferenceScript Era
convertRefScriptToEra :: forall era. ReferenceScript era -> ReferenceScript Era
convertRefScriptToEra ReferenceScript era
ReferenceScriptNone = ReferenceScript Era
forall era. ReferenceScript era
ReferenceScriptNone
convertRefScriptToEra (ReferenceScript BabbageEraOnwards era
_ ScriptInAnyLang
scriptInAnyLang) = BabbageEraOnwards Era -> ScriptInAnyLang -> ReferenceScript Era
forall era.
BabbageEraOnwards era -> ScriptInAnyLang -> ReferenceScript era
ReferenceScript BabbageEraOnwards Era
forall era. IsBabbageBasedEra era => BabbageEraOnwards era
babbageBasedEra ScriptInAnyLang
scriptInAnyLang
toApi :: UTxO -> Cardano.Api.UTxO Era
toApi :: UTxO -> UTxO Era
toApi = UTxO -> UTxO Era
forall a b. Coercible a b => a -> b
coerce