module Blockfrost.Types.Cardano.Transactions
( Transaction (..)
, TransactionUtxos (..)
, UtxoInput (..)
, UtxoOutput (..)
, TransactionRedeemer (..)
, TransactionStake (..)
, TransactionDelegation (..)
, TransactionWithdrawal (..)
, Pot (..)
, TransactionMir (..)
, TransactionPoolUpdate (..)
, PoolUpdateMetadata (..)
, TransactionPoolRetiring (..)
, TransactionMetaJSON (..)
, TransactionMetaCBOR (..)
) where
import Data.Aeson (Value, object, (.=))
import Data.Text (Text)
import Deriving.Aeson
import qualified Money
import Servant.Docs (ToSample (..), samples, singleSample)
import Blockfrost.Types.Cardano.Pools
import Blockfrost.Types.Cardano.Scripts (InlineDatum (..), ScriptDatumCBOR (..))
import Blockfrost.Types.Shared
data Transaction = Transaction
{ Transaction -> Text
_transactionHash :: Text
, Transaction -> BlockHash
_transactionBlock :: BlockHash
, Transaction -> Integer
_transactionBlockHeight :: Integer
, Transaction -> Slot
_transactionSlot :: Slot
, Transaction -> Integer
_transactionIndex :: Integer
, Transaction -> [Amount]
_transactionOutputAmount :: [Amount]
, Transaction -> Lovelaces
_transactionFees :: Lovelaces
, Transaction -> Lovelaces
_transactionDeposit :: Lovelaces
, Transaction -> Integer
_transactionSize :: Integer
, Transaction -> Maybe Text
_transactionInvalidBefore :: Maybe Text
, Transaction -> Maybe Text
_transactionInvalidHereafter :: Maybe Text
, Transaction -> Integer
_transactionUtxoCount :: Integer
, Transaction -> Integer
_transactionWithdrawalCount :: Integer
, Transaction -> Integer
_transactionMirCertCount :: Integer
, Transaction -> Integer
_transactionDelegationCount :: Integer
, Transaction -> Integer
_transactionStakeCertCount :: Integer
, Transaction -> Integer
_transactionPoolUpdateCount :: Integer
, Transaction -> Integer
_transactionPoolRetireCount :: Integer
, Transaction -> Integer
_transactionAssetMintOrBurnCount :: Integer
, Transaction -> Integer
_transactionRedeemerCount :: Integer
, Transaction -> Bool
_transactionValidContract :: Bool
}
deriving stock (Int -> Transaction -> ShowS
[Transaction] -> ShowS
Transaction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Transaction] -> ShowS
$cshowList :: [Transaction] -> ShowS
show :: Transaction -> String
$cshow :: Transaction -> String
showsPrec :: Int -> Transaction -> ShowS
$cshowsPrec :: Int -> Transaction -> ShowS
Show, Transaction -> Transaction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Transaction -> Transaction -> Bool
$c/= :: Transaction -> Transaction -> Bool
== :: Transaction -> Transaction -> Bool
$c== :: Transaction -> Transaction -> Bool
Eq, forall x. Rep Transaction x -> Transaction
forall x. Transaction -> Rep Transaction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Transaction x -> Transaction
$cfrom :: forall x. Transaction -> Rep Transaction x
Generic)
deriving (Value -> Parser [Transaction]
Value -> Parser Transaction
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Transaction]
$cparseJSONList :: Value -> Parser [Transaction]
parseJSON :: Value -> Parser Transaction
$cparseJSON :: Value -> Parser Transaction
FromJSON, [Transaction] -> Encoding
[Transaction] -> Value
Transaction -> Encoding
Transaction -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Transaction] -> Encoding
$ctoEncodingList :: [Transaction] -> Encoding
toJSONList :: [Transaction] -> Value
$ctoJSONList :: [Transaction] -> Value
toEncoding :: Transaction -> Encoding
$ctoEncoding :: Transaction -> Encoding
toJSON :: Transaction -> Value
$ctoJSON :: Transaction -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_transaction", CamelToSnake]] Transaction
instance ToSample Transaction where
toSamples :: Proxy Transaction -> [(Text, Transaction)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample
Transaction
{ _transactionHash :: Text
_transactionHash = Text
"1e043f100dce12d107f679685acd2fc0610e10f72a92d412794c9773d11d8477"
, _transactionBlock :: BlockHash
_transactionBlock = BlockHash
"356b7d7dbb696ccd12775c016941057a9dc70898d87a63fc752271bb46856940"
, _transactionBlockHeight :: Integer
_transactionBlockHeight = Integer
123456
, _transactionSlot :: Slot
_transactionSlot = Slot
42000000
, _transactionIndex :: Integer
_transactionIndex = Integer
1
, _transactionOutputAmount :: [Amount]
_transactionOutputAmount = [Amount]
sampleAmounts
, _transactionFees :: Lovelaces
_transactionFees = Discrete' "ADA" '(1000000, 1)
182485
, _transactionDeposit :: Lovelaces
_transactionDeposit = Discrete' "ADA" '(1000000, 1)
0
, _transactionSize :: Integer
_transactionSize = Integer
433
, _transactionInvalidBefore :: Maybe Text
_transactionInvalidBefore = forall a. Maybe a
Nothing
, _transactionInvalidHereafter :: Maybe Text
_transactionInvalidHereafter = forall a. a -> Maybe a
Just Text
"13885913"
, _transactionUtxoCount :: Integer
_transactionUtxoCount = Integer
4
, _transactionWithdrawalCount :: Integer
_transactionWithdrawalCount = Integer
0
, _transactionMirCertCount :: Integer
_transactionMirCertCount = Integer
0
, _transactionDelegationCount :: Integer
_transactionDelegationCount = Integer
0
, _transactionStakeCertCount :: Integer
_transactionStakeCertCount = Integer
0
, _transactionPoolUpdateCount :: Integer
_transactionPoolUpdateCount = Integer
0
, _transactionPoolRetireCount :: Integer
_transactionPoolRetireCount = Integer
0
, _transactionAssetMintOrBurnCount :: Integer
_transactionAssetMintOrBurnCount = Integer
0
, _transactionRedeemerCount :: Integer
_transactionRedeemerCount = Integer
0
, _transactionValidContract :: Bool
_transactionValidContract = Bool
True
}
data UtxoInput = UtxoInput
{ UtxoInput -> Address
_utxoInputAddress :: Address
, UtxoInput -> [Amount]
_utxoInputAmount :: [Amount]
, UtxoInput -> TxHash
_utxoInputTxHash :: TxHash
, UtxoInput -> Integer
_utxoInputOutputIndex :: Integer
, UtxoInput -> Bool
_utxoInputCollateral :: Bool
, UtxoInput -> Maybe DatumHash
_utxoInputDataHash :: Maybe DatumHash
, UtxoInput -> Maybe InlineDatum
_utxoInputInlineDatum :: Maybe InlineDatum
, UtxoInput -> Maybe ScriptHash
_utxoInputReferenceScriptHash :: Maybe ScriptHash
, UtxoInput -> Bool
_utxoInputReference :: Bool
}
deriving stock (Int -> UtxoInput -> ShowS
[UtxoInput] -> ShowS
UtxoInput -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UtxoInput] -> ShowS
$cshowList :: [UtxoInput] -> ShowS
show :: UtxoInput -> String
$cshow :: UtxoInput -> String
showsPrec :: Int -> UtxoInput -> ShowS
$cshowsPrec :: Int -> UtxoInput -> ShowS
Show, UtxoInput -> UtxoInput -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UtxoInput -> UtxoInput -> Bool
$c/= :: UtxoInput -> UtxoInput -> Bool
== :: UtxoInput -> UtxoInput -> Bool
$c== :: UtxoInput -> UtxoInput -> Bool
Eq, forall x. Rep UtxoInput x -> UtxoInput
forall x. UtxoInput -> Rep UtxoInput x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UtxoInput x -> UtxoInput
$cfrom :: forall x. UtxoInput -> Rep UtxoInput x
Generic)
deriving (Value -> Parser [UtxoInput]
Value -> Parser UtxoInput
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [UtxoInput]
$cparseJSONList :: Value -> Parser [UtxoInput]
parseJSON :: Value -> Parser UtxoInput
$cparseJSON :: Value -> Parser UtxoInput
FromJSON, [UtxoInput] -> Encoding
[UtxoInput] -> Value
UtxoInput -> Encoding
UtxoInput -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [UtxoInput] -> Encoding
$ctoEncodingList :: [UtxoInput] -> Encoding
toJSONList :: [UtxoInput] -> Value
$ctoJSONList :: [UtxoInput] -> Value
toEncoding :: UtxoInput -> Encoding
$ctoEncoding :: UtxoInput -> Encoding
toJSON :: UtxoInput -> Value
$ctoJSON :: UtxoInput -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_utxoInput", CamelToSnake]] UtxoInput
instance ToSample UtxoInput where
toSamples :: Proxy UtxoInput -> [(Text, UtxoInput)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample UtxoInput
utxoInSample
utxoInSample :: UtxoInput
utxoInSample :: UtxoInput
utxoInSample =
UtxoInput
{ _utxoInputAddress :: Address
_utxoInputAddress = Address
"addr1q9ld26v2lv8wvrxxmvg90pn8n8n5k6tdst06q2s856rwmvnueldzuuqmnsye359fqrk8hwvenjnqultn7djtrlft7jnq7dy7wv"
, _utxoInputAmount :: [Amount]
_utxoInputAmount = [Amount]
sampleAmounts
, _utxoInputTxHash :: TxHash
_utxoInputTxHash = TxHash
"1a0570af966fb355a7160e4f82d5a80b8681b7955f5d44bec0dce628516157f0"
, _utxoInputOutputIndex :: Integer
_utxoInputOutputIndex = Integer
0
, _utxoInputCollateral :: Bool
_utxoInputCollateral = Bool
False
, _utxoInputDataHash :: Maybe DatumHash
_utxoInputDataHash = forall a. a -> Maybe a
Just DatumHash
"9e478573ab81ea7a8e31891ce0648b81229f408d596a3483e6f4f9b92d3cf710"
, _utxoInputInlineDatum :: Maybe InlineDatum
_utxoInputInlineDatum = forall a. Maybe a
Nothing
, _utxoInputReferenceScriptHash :: Maybe ScriptHash
_utxoInputReferenceScriptHash = forall a. a -> Maybe a
Just ScriptHash
"13a3efd825703a352a8f71f4e2758d08c28c564e8dfcce9f77776ad1"
, _utxoInputReference :: Bool
_utxoInputReference = Bool
False
}
data UtxoOutput = UtxoOutput
{ UtxoOutput -> Address
_utxoOutputAddress :: Address
, UtxoOutput -> [Amount]
_utxoOutputAmount :: [Amount]
, UtxoOutput -> Maybe DatumHash
_utxoOutputDataHash :: Maybe DatumHash
, UtxoOutput -> Integer
_utxoOutputOutputIndex :: Integer
, UtxoOutput -> Bool
_utxoOutputCollateral :: Bool
, UtxoOutput -> Maybe InlineDatum
_utxoOutputInlineDatum :: Maybe InlineDatum
, UtxoOutput -> Maybe ScriptHash
_utxoOutputReferenceScriptHash :: Maybe ScriptHash
} deriving stock (Int -> UtxoOutput -> ShowS
[UtxoOutput] -> ShowS
UtxoOutput -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UtxoOutput] -> ShowS
$cshowList :: [UtxoOutput] -> ShowS
show :: UtxoOutput -> String
$cshow :: UtxoOutput -> String
showsPrec :: Int -> UtxoOutput -> ShowS
$cshowsPrec :: Int -> UtxoOutput -> ShowS
Show, UtxoOutput -> UtxoOutput -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UtxoOutput -> UtxoOutput -> Bool
$c/= :: UtxoOutput -> UtxoOutput -> Bool
== :: UtxoOutput -> UtxoOutput -> Bool
$c== :: UtxoOutput -> UtxoOutput -> Bool
Eq, forall x. Rep UtxoOutput x -> UtxoOutput
forall x. UtxoOutput -> Rep UtxoOutput x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UtxoOutput x -> UtxoOutput
$cfrom :: forall x. UtxoOutput -> Rep UtxoOutput x
Generic)
deriving (Value -> Parser [UtxoOutput]
Value -> Parser UtxoOutput
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [UtxoOutput]
$cparseJSONList :: Value -> Parser [UtxoOutput]
parseJSON :: Value -> Parser UtxoOutput
$cparseJSON :: Value -> Parser UtxoOutput
FromJSON, [UtxoOutput] -> Encoding
[UtxoOutput] -> Value
UtxoOutput -> Encoding
UtxoOutput -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [UtxoOutput] -> Encoding
$ctoEncodingList :: [UtxoOutput] -> Encoding
toJSONList :: [UtxoOutput] -> Value
$ctoJSONList :: [UtxoOutput] -> Value
toEncoding :: UtxoOutput -> Encoding
$ctoEncoding :: UtxoOutput -> Encoding
toJSON :: UtxoOutput -> Value
$ctoJSON :: UtxoOutput -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_utxoOutput", CamelToSnake]] UtxoOutput
instance ToSample UtxoOutput where
toSamples :: Proxy UtxoOutput -> [(Text, UtxoOutput)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample UtxoOutput
utxoOutSample
utxoOutSample :: UtxoOutput
utxoOutSample :: UtxoOutput
utxoOutSample =
UtxoOutput
{ _utxoOutputAddress :: Address
_utxoOutputAddress = Address
"addr1q9ld26v2lv8wvrxxmvg90pn8n8n5k6tdst06q2s856rwmvnueldzuuqmnsye359fqrk8hwvenjnqultn7djtrlft7jnq7dy7wv"
, _utxoOutputAmount :: [Amount]
_utxoOutputAmount = [Amount]
sampleAmounts
, _utxoOutputDataHash :: Maybe DatumHash
_utxoOutputDataHash = forall a. a -> Maybe a
Just DatumHash
"9e478573ab81ea7a8e31891ce0648b81229f408d596a3483e6f4f9b92d3cf710"
, _utxoOutputOutputIndex :: Integer
_utxoOutputOutputIndex = Integer
0
, _utxoOutputCollateral :: Bool
_utxoOutputCollateral = Bool
False
, _utxoOutputInlineDatum :: Maybe InlineDatum
_utxoOutputInlineDatum = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ ScriptDatumCBOR -> InlineDatum
InlineDatum forall a b. (a -> b) -> a -> b
$ Text -> ScriptDatumCBOR
ScriptDatumCBOR Text
"19a6aa"
, _utxoOutputReferenceScriptHash :: Maybe ScriptHash
_utxoOutputReferenceScriptHash = forall a. a -> Maybe a
Just ScriptHash
"13a3efd825703a352a8f71f4e2758d08c28c564e8dfcce9f77776ad1"
}
data TransactionUtxos = TransactionUtxos
{ TransactionUtxos -> TxHash
_transactionUtxosHash :: TxHash
, TransactionUtxos -> [UtxoInput]
_transactionUtxosInputs :: [UtxoInput]
, TransactionUtxos -> [UtxoOutput]
_transactionUtxosOutputs :: [UtxoOutput]
}
deriving stock (Int -> TransactionUtxos -> ShowS
[TransactionUtxos] -> ShowS
TransactionUtxos -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionUtxos] -> ShowS
$cshowList :: [TransactionUtxos] -> ShowS
show :: TransactionUtxos -> String
$cshow :: TransactionUtxos -> String
showsPrec :: Int -> TransactionUtxos -> ShowS
$cshowsPrec :: Int -> TransactionUtxos -> ShowS
Show, TransactionUtxos -> TransactionUtxos -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionUtxos -> TransactionUtxos -> Bool
$c/= :: TransactionUtxos -> TransactionUtxos -> Bool
== :: TransactionUtxos -> TransactionUtxos -> Bool
$c== :: TransactionUtxos -> TransactionUtxos -> Bool
Eq, forall x. Rep TransactionUtxos x -> TransactionUtxos
forall x. TransactionUtxos -> Rep TransactionUtxos x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransactionUtxos x -> TransactionUtxos
$cfrom :: forall x. TransactionUtxos -> Rep TransactionUtxos x
Generic)
deriving (Value -> Parser [TransactionUtxos]
Value -> Parser TransactionUtxos
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransactionUtxos]
$cparseJSONList :: Value -> Parser [TransactionUtxos]
parseJSON :: Value -> Parser TransactionUtxos
$cparseJSON :: Value -> Parser TransactionUtxos
FromJSON, [TransactionUtxos] -> Encoding
[TransactionUtxos] -> Value
TransactionUtxos -> Encoding
TransactionUtxos -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransactionUtxos] -> Encoding
$ctoEncodingList :: [TransactionUtxos] -> Encoding
toJSONList :: [TransactionUtxos] -> Value
$ctoJSONList :: [TransactionUtxos] -> Value
toEncoding :: TransactionUtxos -> Encoding
$ctoEncoding :: TransactionUtxos -> Encoding
toJSON :: TransactionUtxos -> Value
$ctoJSON :: TransactionUtxos -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_transactionUtxos", CamelToSnake]] TransactionUtxos
instance ToSample TransactionUtxos where
toSamples :: Proxy TransactionUtxos -> [(Text, TransactionUtxos)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample
TransactionUtxos
{ _transactionUtxosHash :: TxHash
_transactionUtxosHash = TxHash
"1e043f100dce12d107f679685acd2fc0610e10f72a92d412794c9773d11d8477"
, _transactionUtxosInputs :: [UtxoInput]
_transactionUtxosInputs = forall (f :: * -> *) a. Applicative f => a -> f a
pure UtxoInput
utxoInSample
, _transactionUtxosOutputs :: [UtxoOutput]
_transactionUtxosOutputs = forall (f :: * -> *) a. Applicative f => a -> f a
pure UtxoOutput
utxoOutSample
}
sampleAmounts :: [Amount]
sampleAmounts :: [Amount]
sampleAmounts =
[ Lovelaces -> Amount
AdaAmount Discrete' "ADA" '(1000000, 1)
42000000
, SomeDiscrete -> Amount
AssetAmount
forall a b. (a -> b) -> a -> b
$ Text -> Scale -> Integer -> SomeDiscrete
Money.mkSomeDiscrete
Text
"b0d07d45fe9514f80213f4020e5a61241458be626841cde717cb38a76e7574636f696e"
Scale
unitScale
Integer
12
]
data TransactionRedeemer = TransactionRedeemer
{ TransactionRedeemer -> Integer
_transactionRedeemerTxIndex :: Integer
, TransactionRedeemer -> ValidationPurpose
_transactionRedeemerPurpose :: ValidationPurpose
, TransactionRedeemer -> ScriptHash
_transactionRedeemerScriptHash:: ScriptHash
, TransactionRedeemer -> DatumHash
_transactionRedeemerRedeemerDataHash :: DatumHash
, TransactionRedeemer -> DatumHash
_transactionRedeemerDatumHash :: DatumHash
, TransactionRedeemer -> Quantity
_transactionRedeemerUnitMem :: Quantity
, TransactionRedeemer -> Quantity
_transactionRedeemerUnitSteps :: Quantity
, TransactionRedeemer -> Lovelaces
_transactionRedeemerFee :: Lovelaces
}
deriving stock (Int -> TransactionRedeemer -> ShowS
[TransactionRedeemer] -> ShowS
TransactionRedeemer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionRedeemer] -> ShowS
$cshowList :: [TransactionRedeemer] -> ShowS
show :: TransactionRedeemer -> String
$cshow :: TransactionRedeemer -> String
showsPrec :: Int -> TransactionRedeemer -> ShowS
$cshowsPrec :: Int -> TransactionRedeemer -> ShowS
Show, TransactionRedeemer -> TransactionRedeemer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionRedeemer -> TransactionRedeemer -> Bool
$c/= :: TransactionRedeemer -> TransactionRedeemer -> Bool
== :: TransactionRedeemer -> TransactionRedeemer -> Bool
$c== :: TransactionRedeemer -> TransactionRedeemer -> Bool
Eq, forall x. Rep TransactionRedeemer x -> TransactionRedeemer
forall x. TransactionRedeemer -> Rep TransactionRedeemer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransactionRedeemer x -> TransactionRedeemer
$cfrom :: forall x. TransactionRedeemer -> Rep TransactionRedeemer x
Generic)
deriving (Value -> Parser [TransactionRedeemer]
Value -> Parser TransactionRedeemer
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransactionRedeemer]
$cparseJSONList :: Value -> Parser [TransactionRedeemer]
parseJSON :: Value -> Parser TransactionRedeemer
$cparseJSON :: Value -> Parser TransactionRedeemer
FromJSON, [TransactionRedeemer] -> Encoding
[TransactionRedeemer] -> Value
TransactionRedeemer -> Encoding
TransactionRedeemer -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransactionRedeemer] -> Encoding
$ctoEncodingList :: [TransactionRedeemer] -> Encoding
toJSONList :: [TransactionRedeemer] -> Value
$ctoJSONList :: [TransactionRedeemer] -> Value
toEncoding :: TransactionRedeemer -> Encoding
$ctoEncoding :: TransactionRedeemer -> Encoding
toJSON :: TransactionRedeemer -> Value
$ctoJSON :: TransactionRedeemer -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_transactionRedeemer", CamelToSnake]] TransactionRedeemer
instance ToSample TransactionRedeemer where
toSamples :: Proxy TransactionRedeemer -> [(Text, TransactionRedeemer)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample
TransactionRedeemer
{ _transactionRedeemerTxIndex :: Integer
_transactionRedeemerTxIndex = Integer
0
, _transactionRedeemerPurpose :: ValidationPurpose
_transactionRedeemerPurpose = ValidationPurpose
Spend
, _transactionRedeemerScriptHash :: ScriptHash
_transactionRedeemerScriptHash = ScriptHash
"ec26b89af41bef0f7585353831cb5da42b5b37185e0c8a526143b824"
, _transactionRedeemerRedeemerDataHash :: DatumHash
_transactionRedeemerRedeemerDataHash = DatumHash
"923918e403bf43c34b4ef6b48eb2ee04babed17320d8d1b9ff9ad086e86f44ec"
, _transactionRedeemerDatumHash :: DatumHash
_transactionRedeemerDatumHash = DatumHash
"923918e403bf43c34b4ef6b48eb2ee04babed17320d8d1b9ff9ad086e86f44ec"
, _transactionRedeemerUnitMem :: Quantity
_transactionRedeemerUnitMem = Quantity
1700
, _transactionRedeemerUnitSteps :: Quantity
_transactionRedeemerUnitSteps = Quantity
476468
, _transactionRedeemerFee :: Lovelaces
_transactionRedeemerFee = Discrete' "ADA" '(1000000, 1)
172033
}
data TransactionStake = TransactionStake
{ TransactionStake -> Integer
_transactionStakeCertIndex :: Integer
, TransactionStake -> Address
_transactionStakeAddress :: Address
, TransactionStake -> Bool
_transactionStakeRegistration :: Bool
}
deriving stock (Int -> TransactionStake -> ShowS
[TransactionStake] -> ShowS
TransactionStake -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionStake] -> ShowS
$cshowList :: [TransactionStake] -> ShowS
show :: TransactionStake -> String
$cshow :: TransactionStake -> String
showsPrec :: Int -> TransactionStake -> ShowS
$cshowsPrec :: Int -> TransactionStake -> ShowS
Show, TransactionStake -> TransactionStake -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionStake -> TransactionStake -> Bool
$c/= :: TransactionStake -> TransactionStake -> Bool
== :: TransactionStake -> TransactionStake -> Bool
$c== :: TransactionStake -> TransactionStake -> Bool
Eq, forall x. Rep TransactionStake x -> TransactionStake
forall x. TransactionStake -> Rep TransactionStake x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransactionStake x -> TransactionStake
$cfrom :: forall x. TransactionStake -> Rep TransactionStake x
Generic)
deriving (Value -> Parser [TransactionStake]
Value -> Parser TransactionStake
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransactionStake]
$cparseJSONList :: Value -> Parser [TransactionStake]
parseJSON :: Value -> Parser TransactionStake
$cparseJSON :: Value -> Parser TransactionStake
FromJSON, [TransactionStake] -> Encoding
[TransactionStake] -> Value
TransactionStake -> Encoding
TransactionStake -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransactionStake] -> Encoding
$ctoEncodingList :: [TransactionStake] -> Encoding
toJSONList :: [TransactionStake] -> Value
$ctoJSONList :: [TransactionStake] -> Value
toEncoding :: TransactionStake -> Encoding
$ctoEncoding :: TransactionStake -> Encoding
toJSON :: TransactionStake -> Value
$ctoJSON :: TransactionStake -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_transactionStake", CamelToSnake]] TransactionStake
instance ToSample TransactionStake where
toSamples :: Proxy TransactionStake -> [(Text, TransactionStake)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample
TransactionStake
{ _transactionStakeCertIndex :: Integer
_transactionStakeCertIndex = Integer
0
, _transactionStakeAddress :: Address
_transactionStakeAddress = Address
"stake1u9t3a0tcwune5xrnfjg4q7cpvjlgx9lcv0cuqf5mhfjwrvcwrulda"
, _transactionStakeRegistration :: Bool
_transactionStakeRegistration = Bool
True
}
data TransactionDelegation = TransactionDelegation
{ TransactionDelegation -> Integer
_transactionDelegationCertIndex :: Integer
, TransactionDelegation -> Address
_transactionDelegationAddress :: Address
, TransactionDelegation -> PoolId
_transactionDelegationPoolId :: PoolId
, TransactionDelegation -> Epoch
_transactionDelegationActiveEpoch :: Epoch
}
deriving stock (Int -> TransactionDelegation -> ShowS
[TransactionDelegation] -> ShowS
TransactionDelegation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionDelegation] -> ShowS
$cshowList :: [TransactionDelegation] -> ShowS
show :: TransactionDelegation -> String
$cshow :: TransactionDelegation -> String
showsPrec :: Int -> TransactionDelegation -> ShowS
$cshowsPrec :: Int -> TransactionDelegation -> ShowS
Show, TransactionDelegation -> TransactionDelegation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionDelegation -> TransactionDelegation -> Bool
$c/= :: TransactionDelegation -> TransactionDelegation -> Bool
== :: TransactionDelegation -> TransactionDelegation -> Bool
$c== :: TransactionDelegation -> TransactionDelegation -> Bool
Eq, forall x. Rep TransactionDelegation x -> TransactionDelegation
forall x. TransactionDelegation -> Rep TransactionDelegation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransactionDelegation x -> TransactionDelegation
$cfrom :: forall x. TransactionDelegation -> Rep TransactionDelegation x
Generic)
deriving (Value -> Parser [TransactionDelegation]
Value -> Parser TransactionDelegation
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransactionDelegation]
$cparseJSONList :: Value -> Parser [TransactionDelegation]
parseJSON :: Value -> Parser TransactionDelegation
$cparseJSON :: Value -> Parser TransactionDelegation
FromJSON, [TransactionDelegation] -> Encoding
[TransactionDelegation] -> Value
TransactionDelegation -> Encoding
TransactionDelegation -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransactionDelegation] -> Encoding
$ctoEncodingList :: [TransactionDelegation] -> Encoding
toJSONList :: [TransactionDelegation] -> Value
$ctoJSONList :: [TransactionDelegation] -> Value
toEncoding :: TransactionDelegation -> Encoding
$ctoEncoding :: TransactionDelegation -> Encoding
toJSON :: TransactionDelegation -> Value
$ctoJSON :: TransactionDelegation -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_transactionDelegation", CamelToSnake]] TransactionDelegation
instance ToSample TransactionDelegation where
toSamples :: Proxy TransactionDelegation -> [(Text, TransactionDelegation)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample
TransactionDelegation
{ _transactionDelegationCertIndex :: Integer
_transactionDelegationCertIndex = Integer
0
, _transactionDelegationAddress :: Address
_transactionDelegationAddress = Address
"stake1u9t3a0tcwune5xrnfjg4q7cpvjlgx9lcv0cuqf5mhfjwrvcwrulda"
, _transactionDelegationPoolId :: PoolId
_transactionDelegationPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
, _transactionDelegationActiveEpoch :: Epoch
_transactionDelegationActiveEpoch = Epoch
210
}
data TransactionWithdrawal = TransactionWithdrawal
{ TransactionWithdrawal -> Address
_transactionWithdrawalAddress :: Address
, TransactionWithdrawal -> Lovelaces
_transactionWithdrawalAmount :: Lovelaces
}
deriving stock (Int -> TransactionWithdrawal -> ShowS
[TransactionWithdrawal] -> ShowS
TransactionWithdrawal -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionWithdrawal] -> ShowS
$cshowList :: [TransactionWithdrawal] -> ShowS
show :: TransactionWithdrawal -> String
$cshow :: TransactionWithdrawal -> String
showsPrec :: Int -> TransactionWithdrawal -> ShowS
$cshowsPrec :: Int -> TransactionWithdrawal -> ShowS
Show, TransactionWithdrawal -> TransactionWithdrawal -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionWithdrawal -> TransactionWithdrawal -> Bool
$c/= :: TransactionWithdrawal -> TransactionWithdrawal -> Bool
== :: TransactionWithdrawal -> TransactionWithdrawal -> Bool
$c== :: TransactionWithdrawal -> TransactionWithdrawal -> Bool
Eq, forall x. Rep TransactionWithdrawal x -> TransactionWithdrawal
forall x. TransactionWithdrawal -> Rep TransactionWithdrawal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransactionWithdrawal x -> TransactionWithdrawal
$cfrom :: forall x. TransactionWithdrawal -> Rep TransactionWithdrawal x
Generic)
deriving (Value -> Parser [TransactionWithdrawal]
Value -> Parser TransactionWithdrawal
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransactionWithdrawal]
$cparseJSONList :: Value -> Parser [TransactionWithdrawal]
parseJSON :: Value -> Parser TransactionWithdrawal
$cparseJSON :: Value -> Parser TransactionWithdrawal
FromJSON, [TransactionWithdrawal] -> Encoding
[TransactionWithdrawal] -> Value
TransactionWithdrawal -> Encoding
TransactionWithdrawal -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransactionWithdrawal] -> Encoding
$ctoEncodingList :: [TransactionWithdrawal] -> Encoding
toJSONList :: [TransactionWithdrawal] -> Value
$ctoJSONList :: [TransactionWithdrawal] -> Value
toEncoding :: TransactionWithdrawal -> Encoding
$ctoEncoding :: TransactionWithdrawal -> Encoding
toJSON :: TransactionWithdrawal -> Value
$ctoJSON :: TransactionWithdrawal -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_transactionWithdrawal", CamelToSnake]] TransactionWithdrawal
instance ToSample TransactionWithdrawal where
toSamples :: Proxy TransactionWithdrawal -> [(Text, TransactionWithdrawal)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample
TransactionWithdrawal
{ _transactionWithdrawalAddress :: Address
_transactionWithdrawalAddress = Address
"stake1u9r76ypf5fskppa0cmttas05cgcswrttn6jrq4yd7jpdnvc7gt0yc"
, _transactionWithdrawalAmount :: Lovelaces
_transactionWithdrawalAmount = Discrete' "ADA" '(1000000, 1)
431833601
}
data Pot = Reserve | Treasury
deriving stock (Int -> Pot -> ShowS
[Pot] -> ShowS
Pot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Pot] -> ShowS
$cshowList :: [Pot] -> ShowS
show :: Pot -> String
$cshow :: Pot -> String
showsPrec :: Int -> Pot -> ShowS
$cshowsPrec :: Int -> Pot -> ShowS
Show, Pot -> Pot -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Pot -> Pot -> Bool
$c/= :: Pot -> Pot -> Bool
== :: Pot -> Pot -> Bool
$c== :: Pot -> Pot -> Bool
Eq, forall x. Rep Pot x -> Pot
forall x. Pot -> Rep Pot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Pot x -> Pot
$cfrom :: forall x. Pot -> Rep Pot x
Generic)
deriving (Value -> Parser [Pot]
Value -> Parser Pot
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Pot]
$cparseJSONList :: Value -> Parser [Pot]
parseJSON :: Value -> Parser Pot
$cparseJSON :: Value -> Parser Pot
FromJSON, [Pot] -> Encoding
[Pot] -> Value
Pot -> Encoding
Pot -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Pot] -> Encoding
$ctoEncodingList :: [Pot] -> Encoding
toJSONList :: [Pot] -> Value
$ctoJSONList :: [Pot] -> Value
toEncoding :: Pot -> Encoding
$ctoEncoding :: Pot -> Encoding
toJSON :: Pot -> Value
$ctoJSON :: Pot -> Value
ToJSON)
via CustomJSON '[ConstructorTagModifier '[ToLower]] Pot
instance ToSample Pot where
toSamples :: Proxy Pot -> [(Text, Pot)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [(Text, a)]
samples [ Pot
Reserve, Pot
Treasury ]
data TransactionMir = TransactionMir
{ TransactionMir -> Pot
_transactionMirPot :: Pot
, TransactionMir -> Integer
_transactionMirCertIndex :: Integer
, TransactionMir -> Address
_transactionMirAddress :: Address
, TransactionMir -> Lovelaces
_transactionMirAmount :: Lovelaces
}
deriving stock (Int -> TransactionMir -> ShowS
[TransactionMir] -> ShowS
TransactionMir -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionMir] -> ShowS
$cshowList :: [TransactionMir] -> ShowS
show :: TransactionMir -> String
$cshow :: TransactionMir -> String
showsPrec :: Int -> TransactionMir -> ShowS
$cshowsPrec :: Int -> TransactionMir -> ShowS
Show, TransactionMir -> TransactionMir -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionMir -> TransactionMir -> Bool
$c/= :: TransactionMir -> TransactionMir -> Bool
== :: TransactionMir -> TransactionMir -> Bool
$c== :: TransactionMir -> TransactionMir -> Bool
Eq, forall x. Rep TransactionMir x -> TransactionMir
forall x. TransactionMir -> Rep TransactionMir x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransactionMir x -> TransactionMir
$cfrom :: forall x. TransactionMir -> Rep TransactionMir x
Generic)
deriving (Value -> Parser [TransactionMir]
Value -> Parser TransactionMir
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransactionMir]
$cparseJSONList :: Value -> Parser [TransactionMir]
parseJSON :: Value -> Parser TransactionMir
$cparseJSON :: Value -> Parser TransactionMir
FromJSON, [TransactionMir] -> Encoding
[TransactionMir] -> Value
TransactionMir -> Encoding
TransactionMir -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransactionMir] -> Encoding
$ctoEncodingList :: [TransactionMir] -> Encoding
toJSONList :: [TransactionMir] -> Value
$ctoJSONList :: [TransactionMir] -> Value
toEncoding :: TransactionMir -> Encoding
$ctoEncoding :: TransactionMir -> Encoding
toJSON :: TransactionMir -> Value
$ctoJSON :: TransactionMir -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_transactionMir", CamelToSnake]] TransactionMir
instance ToSample TransactionMir where
toSamples :: Proxy TransactionMir -> [(Text, TransactionMir)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample
TransactionMir
{ _transactionMirPot :: Pot
_transactionMirPot = Pot
Reserve
, _transactionMirCertIndex :: Integer
_transactionMirCertIndex = Integer
0
, _transactionMirAddress :: Address
_transactionMirAddress = Address
"stake1u9r76ypf5fskppa0cmttas05cgcswrttn6jrq4yd7jpdnvc7gt0yc"
, _transactionMirAmount :: Lovelaces
_transactionMirAmount = Discrete' "ADA" '(1000000, 1)
431833601
}
data TransactionPoolUpdate = TransactionPoolUpdate
{ TransactionPoolUpdate -> Integer
_transactionPoolUpdateCertIndex :: Integer
, TransactionPoolUpdate -> PoolId
_transactionPoolUpdatePoolId :: PoolId
, TransactionPoolUpdate -> Text
_transactionPoolUpdateVrfKey :: Text
, TransactionPoolUpdate -> Lovelaces
_transactionPoolUpdatePledge :: Lovelaces
, TransactionPoolUpdate -> Double
_transactionPoolUpdateMarginCost :: Double
, TransactionPoolUpdate -> Lovelaces
_transactionPoolUpdateFixedCost :: Lovelaces
, TransactionPoolUpdate -> Address
_transactionPoolUpdateRewardAccount :: Address
, TransactionPoolUpdate -> [Address]
_transactionPoolUpdateOwners :: [Address]
, TransactionPoolUpdate -> Maybe PoolUpdateMetadata
_transactionPoolUpdateMetadata :: Maybe PoolUpdateMetadata
, TransactionPoolUpdate -> [PoolRelay]
_transactionPoolUpdateRelays :: [PoolRelay]
, TransactionPoolUpdate -> Epoch
_transactionPoolUpdateActiveEpoch :: Epoch
}
deriving stock (Int -> TransactionPoolUpdate -> ShowS
[TransactionPoolUpdate] -> ShowS
TransactionPoolUpdate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionPoolUpdate] -> ShowS
$cshowList :: [TransactionPoolUpdate] -> ShowS
show :: TransactionPoolUpdate -> String
$cshow :: TransactionPoolUpdate -> String
showsPrec :: Int -> TransactionPoolUpdate -> ShowS
$cshowsPrec :: Int -> TransactionPoolUpdate -> ShowS
Show, TransactionPoolUpdate -> TransactionPoolUpdate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionPoolUpdate -> TransactionPoolUpdate -> Bool
$c/= :: TransactionPoolUpdate -> TransactionPoolUpdate -> Bool
== :: TransactionPoolUpdate -> TransactionPoolUpdate -> Bool
$c== :: TransactionPoolUpdate -> TransactionPoolUpdate -> Bool
Eq, forall x. Rep TransactionPoolUpdate x -> TransactionPoolUpdate
forall x. TransactionPoolUpdate -> Rep TransactionPoolUpdate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransactionPoolUpdate x -> TransactionPoolUpdate
$cfrom :: forall x. TransactionPoolUpdate -> Rep TransactionPoolUpdate x
Generic)
deriving (Value -> Parser [TransactionPoolUpdate]
Value -> Parser TransactionPoolUpdate
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransactionPoolUpdate]
$cparseJSONList :: Value -> Parser [TransactionPoolUpdate]
parseJSON :: Value -> Parser TransactionPoolUpdate
$cparseJSON :: Value -> Parser TransactionPoolUpdate
FromJSON, [TransactionPoolUpdate] -> Encoding
[TransactionPoolUpdate] -> Value
TransactionPoolUpdate -> Encoding
TransactionPoolUpdate -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransactionPoolUpdate] -> Encoding
$ctoEncodingList :: [TransactionPoolUpdate] -> Encoding
toJSONList :: [TransactionPoolUpdate] -> Value
$ctoJSONList :: [TransactionPoolUpdate] -> Value
toEncoding :: TransactionPoolUpdate -> Encoding
$ctoEncoding :: TransactionPoolUpdate -> Encoding
toJSON :: TransactionPoolUpdate -> Value
$ctoJSON :: TransactionPoolUpdate -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_transactionPoolUpdate", CamelToSnake]] TransactionPoolUpdate
instance ToSample TransactionPoolUpdate where
toSamples :: Proxy TransactionPoolUpdate -> [(Text, TransactionPoolUpdate)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample
TransactionPoolUpdate
{ _transactionPoolUpdateCertIndex :: Integer
_transactionPoolUpdateCertIndex = Integer
0
, _transactionPoolUpdatePoolId :: PoolId
_transactionPoolUpdatePoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
, _transactionPoolUpdateVrfKey :: Text
_transactionPoolUpdateVrfKey = Text
"0b5245f9934ec2151116fb8ec00f35fd00e0aa3b075c4ed12cce440f999d8233"
, _transactionPoolUpdatePledge :: Lovelaces
_transactionPoolUpdatePledge = Discrete' "ADA" '(1000000, 1)
5000000000
, _transactionPoolUpdateMarginCost :: Double
_transactionPoolUpdateMarginCost = Double
0.05
, _transactionPoolUpdateFixedCost :: Lovelaces
_transactionPoolUpdateFixedCost = Discrete' "ADA" '(1000000, 1)
340000000
, _transactionPoolUpdateRewardAccount :: Address
_transactionPoolUpdateRewardAccount = Address
"stake1uxkptsa4lkr55jleztw43t37vgdn88l6ghclfwuxld2eykgpgvg3f"
, _transactionPoolUpdateOwners :: [Address]
_transactionPoolUpdateOwners = [ Address
"stake1u98nnlkvkk23vtvf9273uq7cph5ww6u2yq2389psuqet90sv4xv9v" ]
, _transactionPoolUpdateMetadata :: Maybe PoolUpdateMetadata
_transactionPoolUpdateMetadata = forall a. a -> Maybe a
Just PoolUpdateMetadata
samplePoolUpdateMetadata
, _transactionPoolUpdateRelays :: [PoolRelay]
_transactionPoolUpdateRelays = [ PoolRelay
samplePoolRelay ]
, _transactionPoolUpdateActiveEpoch :: Epoch
_transactionPoolUpdateActiveEpoch = Epoch
210
}
data TransactionPoolRetiring = TransactionPoolRetiring
{ TransactionPoolRetiring -> Integer
_transactionPoolRetiringCertIndex :: Integer
, TransactionPoolRetiring -> PoolId
_transactionPoolRetiringPoolId :: PoolId
, TransactionPoolRetiring -> Epoch
_transactionPoolRetiringRetiringEpoch :: Epoch
}
deriving stock (Int -> TransactionPoolRetiring -> ShowS
[TransactionPoolRetiring] -> ShowS
TransactionPoolRetiring -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionPoolRetiring] -> ShowS
$cshowList :: [TransactionPoolRetiring] -> ShowS
show :: TransactionPoolRetiring -> String
$cshow :: TransactionPoolRetiring -> String
showsPrec :: Int -> TransactionPoolRetiring -> ShowS
$cshowsPrec :: Int -> TransactionPoolRetiring -> ShowS
Show, TransactionPoolRetiring -> TransactionPoolRetiring -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionPoolRetiring -> TransactionPoolRetiring -> Bool
$c/= :: TransactionPoolRetiring -> TransactionPoolRetiring -> Bool
== :: TransactionPoolRetiring -> TransactionPoolRetiring -> Bool
$c== :: TransactionPoolRetiring -> TransactionPoolRetiring -> Bool
Eq, forall x. Rep TransactionPoolRetiring x -> TransactionPoolRetiring
forall x. TransactionPoolRetiring -> Rep TransactionPoolRetiring x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransactionPoolRetiring x -> TransactionPoolRetiring
$cfrom :: forall x. TransactionPoolRetiring -> Rep TransactionPoolRetiring x
Generic)
deriving (Value -> Parser [TransactionPoolRetiring]
Value -> Parser TransactionPoolRetiring
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransactionPoolRetiring]
$cparseJSONList :: Value -> Parser [TransactionPoolRetiring]
parseJSON :: Value -> Parser TransactionPoolRetiring
$cparseJSON :: Value -> Parser TransactionPoolRetiring
FromJSON, [TransactionPoolRetiring] -> Encoding
[TransactionPoolRetiring] -> Value
TransactionPoolRetiring -> Encoding
TransactionPoolRetiring -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransactionPoolRetiring] -> Encoding
$ctoEncodingList :: [TransactionPoolRetiring] -> Encoding
toJSONList :: [TransactionPoolRetiring] -> Value
$ctoJSONList :: [TransactionPoolRetiring] -> Value
toEncoding :: TransactionPoolRetiring -> Encoding
$ctoEncoding :: TransactionPoolRetiring -> Encoding
toJSON :: TransactionPoolRetiring -> Value
$ctoJSON :: TransactionPoolRetiring -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_transactionPoolRetiring", CamelToSnake]] TransactionPoolRetiring
instance ToSample TransactionPoolRetiring where
toSamples :: Proxy TransactionPoolRetiring -> [(Text, TransactionPoolRetiring)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample
TransactionPoolRetiring
{ _transactionPoolRetiringCertIndex :: Integer
_transactionPoolRetiringCertIndex = Integer
0
, _transactionPoolRetiringPoolId :: PoolId
_transactionPoolRetiringPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
, _transactionPoolRetiringRetiringEpoch :: Epoch
_transactionPoolRetiringRetiringEpoch = Epoch
216
}
data TransactionMetaJSON = TransactionMetaJSON
{ TransactionMetaJSON -> Text
_transactionMetaJSONLabel :: Text
, TransactionMetaJSON -> Maybe Value
_transactionMetaJSONJSONMetadata :: Maybe Value
}
deriving stock (Int -> TransactionMetaJSON -> ShowS
[TransactionMetaJSON] -> ShowS
TransactionMetaJSON -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionMetaJSON] -> ShowS
$cshowList :: [TransactionMetaJSON] -> ShowS
show :: TransactionMetaJSON -> String
$cshow :: TransactionMetaJSON -> String
showsPrec :: Int -> TransactionMetaJSON -> ShowS
$cshowsPrec :: Int -> TransactionMetaJSON -> ShowS
Show, TransactionMetaJSON -> TransactionMetaJSON -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionMetaJSON -> TransactionMetaJSON -> Bool
$c/= :: TransactionMetaJSON -> TransactionMetaJSON -> Bool
== :: TransactionMetaJSON -> TransactionMetaJSON -> Bool
$c== :: TransactionMetaJSON -> TransactionMetaJSON -> Bool
Eq, forall x. Rep TransactionMetaJSON x -> TransactionMetaJSON
forall x. TransactionMetaJSON -> Rep TransactionMetaJSON x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransactionMetaJSON x -> TransactionMetaJSON
$cfrom :: forall x. TransactionMetaJSON -> Rep TransactionMetaJSON x
Generic)
deriving (Value -> Parser [TransactionMetaJSON]
Value -> Parser TransactionMetaJSON
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransactionMetaJSON]
$cparseJSONList :: Value -> Parser [TransactionMetaJSON]
parseJSON :: Value -> Parser TransactionMetaJSON
$cparseJSON :: Value -> Parser TransactionMetaJSON
FromJSON, [TransactionMetaJSON] -> Encoding
[TransactionMetaJSON] -> Value
TransactionMetaJSON -> Encoding
TransactionMetaJSON -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransactionMetaJSON] -> Encoding
$ctoEncodingList :: [TransactionMetaJSON] -> Encoding
toJSONList :: [TransactionMetaJSON] -> Value
$ctoJSONList :: [TransactionMetaJSON] -> Value
toEncoding :: TransactionMetaJSON -> Encoding
$ctoEncoding :: TransactionMetaJSON -> Encoding
toJSON :: TransactionMetaJSON -> Value
$ctoJSON :: TransactionMetaJSON -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_transactionMetaJSON", CamelToSnake]] TransactionMetaJSON
instance ToSample TransactionMetaJSON where
toSamples :: Proxy TransactionMetaJSON -> [(Text, TransactionMetaJSON)]
toSamples =
let oracleMeta :: Text -> Value
oracleMeta Text
val =
[Pair] -> Value
object [
Key
"ADAUSD" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.=
[ [Pair] -> Value
object [ Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (Text
val :: Text)
, Key
"source" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (Text
"ergoOracles" :: Text) ]
]
]
in forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [(Text, a)]
samples
[ Text -> Maybe Value -> TransactionMetaJSON
TransactionMetaJSON
Text
"1967"
(forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object
[ Key
"metadata" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (Text
"https://nut.link/metadata.json" :: Text)
, Key
"hash" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (Text
"6bf124f217d0e5a0a8adb1dbd8540e1334280d49ab861127868339f43b3948af" :: Text)
])
, Text -> Maybe Value -> TransactionMetaJSON
TransactionMetaJSON
Text
"1968"
(forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Text -> Value
oracleMeta Text
"0.15409850555139935")
]
data TransactionMetaCBOR = TransactionMetaCBOR
{ TransactionMetaCBOR -> Text
_transactionMetaCBORLabel :: Text
, TransactionMetaCBOR -> Maybe Text
_transactionMetaCBORMetadata :: Maybe Text
}
deriving stock (Int -> TransactionMetaCBOR -> ShowS
[TransactionMetaCBOR] -> ShowS
TransactionMetaCBOR -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionMetaCBOR] -> ShowS
$cshowList :: [TransactionMetaCBOR] -> ShowS
show :: TransactionMetaCBOR -> String
$cshow :: TransactionMetaCBOR -> String
showsPrec :: Int -> TransactionMetaCBOR -> ShowS
$cshowsPrec :: Int -> TransactionMetaCBOR -> ShowS
Show, TransactionMetaCBOR -> TransactionMetaCBOR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionMetaCBOR -> TransactionMetaCBOR -> Bool
$c/= :: TransactionMetaCBOR -> TransactionMetaCBOR -> Bool
== :: TransactionMetaCBOR -> TransactionMetaCBOR -> Bool
$c== :: TransactionMetaCBOR -> TransactionMetaCBOR -> Bool
Eq, forall x. Rep TransactionMetaCBOR x -> TransactionMetaCBOR
forall x. TransactionMetaCBOR -> Rep TransactionMetaCBOR x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransactionMetaCBOR x -> TransactionMetaCBOR
$cfrom :: forall x. TransactionMetaCBOR -> Rep TransactionMetaCBOR x
Generic)
deriving (Value -> Parser [TransactionMetaCBOR]
Value -> Parser TransactionMetaCBOR
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransactionMetaCBOR]
$cparseJSONList :: Value -> Parser [TransactionMetaCBOR]
parseJSON :: Value -> Parser TransactionMetaCBOR
$cparseJSON :: Value -> Parser TransactionMetaCBOR
FromJSON, [TransactionMetaCBOR] -> Encoding
[TransactionMetaCBOR] -> Value
TransactionMetaCBOR -> Encoding
TransactionMetaCBOR -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransactionMetaCBOR] -> Encoding
$ctoEncodingList :: [TransactionMetaCBOR] -> Encoding
toJSONList :: [TransactionMetaCBOR] -> Value
$ctoJSONList :: [TransactionMetaCBOR] -> Value
toEncoding :: TransactionMetaCBOR -> Encoding
$ctoEncoding :: TransactionMetaCBOR -> Encoding
toJSON :: TransactionMetaCBOR -> Value
$ctoJSON :: TransactionMetaCBOR -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_transactionMetaCBOR", CamelToSnake]] TransactionMetaCBOR
instance ToSample TransactionMetaCBOR where
toSamples :: Proxy TransactionMetaCBOR -> [(Text, TransactionMetaCBOR)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample forall a b. (a -> b) -> a -> b
$
Text -> Maybe Text -> TransactionMetaCBOR
TransactionMetaCBOR
Text
"1968"
(forall a. a -> Maybe a
Just Text
"a100a16b436f6d62696e6174696f6e8601010101010c")
data PoolUpdateMetadata = PoolUpdateMetadata
{ PoolUpdateMetadata -> Maybe Text
_poolUpdateMetadataUrl :: Maybe Text
, PoolUpdateMetadata -> Maybe Text
_poolUpdateMetadataHash :: Maybe Text
, PoolUpdateMetadata -> Maybe Text
_poolUpdateMetadataTicker :: Maybe Text
, PoolUpdateMetadata -> Maybe Text
_poolUpdateMetadataName :: Maybe Text
, PoolUpdateMetadata -> Maybe Text
_poolUpdateMetadataDescription :: Maybe Text
, PoolUpdateMetadata -> Maybe Text
_poolUpdateMetadataHomepage :: Maybe Text
}
deriving stock (Int -> PoolUpdateMetadata -> ShowS
[PoolUpdateMetadata] -> ShowS
PoolUpdateMetadata -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PoolUpdateMetadata] -> ShowS
$cshowList :: [PoolUpdateMetadata] -> ShowS
show :: PoolUpdateMetadata -> String
$cshow :: PoolUpdateMetadata -> String
showsPrec :: Int -> PoolUpdateMetadata -> ShowS
$cshowsPrec :: Int -> PoolUpdateMetadata -> ShowS
Show, PoolUpdateMetadata -> PoolUpdateMetadata -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PoolUpdateMetadata -> PoolUpdateMetadata -> Bool
$c/= :: PoolUpdateMetadata -> PoolUpdateMetadata -> Bool
== :: PoolUpdateMetadata -> PoolUpdateMetadata -> Bool
$c== :: PoolUpdateMetadata -> PoolUpdateMetadata -> Bool
Eq, forall x. Rep PoolUpdateMetadata x -> PoolUpdateMetadata
forall x. PoolUpdateMetadata -> Rep PoolUpdateMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PoolUpdateMetadata x -> PoolUpdateMetadata
$cfrom :: forall x. PoolUpdateMetadata -> Rep PoolUpdateMetadata x
Generic)
deriving (Value -> Parser [PoolUpdateMetadata]
Value -> Parser PoolUpdateMetadata
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PoolUpdateMetadata]
$cparseJSONList :: Value -> Parser [PoolUpdateMetadata]
parseJSON :: Value -> Parser PoolUpdateMetadata
$cparseJSON :: Value -> Parser PoolUpdateMetadata
FromJSON, [PoolUpdateMetadata] -> Encoding
[PoolUpdateMetadata] -> Value
PoolUpdateMetadata -> Encoding
PoolUpdateMetadata -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PoolUpdateMetadata] -> Encoding
$ctoEncodingList :: [PoolUpdateMetadata] -> Encoding
toJSONList :: [PoolUpdateMetadata] -> Value
$ctoJSONList :: [PoolUpdateMetadata] -> Value
toEncoding :: PoolUpdateMetadata -> Encoding
$ctoEncoding :: PoolUpdateMetadata -> Encoding
toJSON :: PoolUpdateMetadata -> Value
$ctoJSON :: PoolUpdateMetadata -> Value
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_poolUpdateMetadata", CamelToSnake]] PoolUpdateMetadata
instance ToSample PoolUpdateMetadata where
toSamples :: Proxy PoolUpdateMetadata -> [(Text, PoolUpdateMetadata)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample PoolUpdateMetadata
samplePoolUpdateMetadata
samplePoolUpdateMetadata :: PoolUpdateMetadata
samplePoolUpdateMetadata :: PoolUpdateMetadata
samplePoolUpdateMetadata =
PoolUpdateMetadata
{ _poolUpdateMetadataUrl :: Maybe Text
_poolUpdateMetadataUrl = forall a. a -> Maybe a
Just Text
"https://stakenuts.com/mainnet.json"
, _poolUpdateMetadataHash :: Maybe Text
_poolUpdateMetadataHash = forall a. a -> Maybe a
Just Text
"47c0c68cb57f4a5b4a87bad896fc274678e7aea98e200fa14a1cb40c0cab1d8c"
, _poolUpdateMetadataTicker :: Maybe Text
_poolUpdateMetadataTicker = forall a. a -> Maybe a
Just Text
"NUTS"
, _poolUpdateMetadataName :: Maybe Text
_poolUpdateMetadataName = forall a. a -> Maybe a
Just Text
"Stake Nuts"
, _poolUpdateMetadataDescription :: Maybe Text
_poolUpdateMetadataDescription = forall a. a -> Maybe a
Just Text
"The best pool ever"
, _poolUpdateMetadataHomepage :: Maybe Text
_poolUpdateMetadataHomepage = forall a. a -> Maybe a
Just Text
"https://stakentus.com/"
}