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