-- | Cardano Transactions responses

module Blockfrost.Types.Cardano.Transactions
  ( Transaction (..)
  , TransactionUtxos (..)
  , UtxoInput (..)
  , UtxoOutput (..)
  , ValidationPurpose (..)
  , 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.Shared

-- | Information about a transaction
data Transaction = Transaction
  { Transaction -> Text
_transactionHash                 :: Text -- ^ Transaction hash
  , Transaction -> BlockHash
_transactionBlock                :: BlockHash -- ^ Block hash
  , Transaction -> Integer
_transactionBlockHeight          :: Integer -- ^ Block number
  , Transaction -> Slot
_transactionSlot                 :: Slot -- ^ Slot number
  , Transaction -> Integer
_transactionIndex                :: Integer -- ^ Transaction index within the block
  , Transaction -> [Amount]
_transactionOutputAmount         :: [Amount] -- ^ Transaction outputs
  , Transaction -> Lovelaces
_transactionFees                 :: Lovelaces -- ^ Fees of the transaction in Lovelaces
  , Transaction -> Lovelaces
_transactionDeposit              :: Lovelaces -- ^ Deposit within the transaction in Lovelaces
  , Transaction -> Integer
_transactionSize                 :: Integer -- ^ Size of the transaction in Bytes
  , Transaction -> Maybe Text
_transactionInvalidBefore        :: Maybe Text -- ^ Left (included) endpoint of the timelock validity intervals
  , Transaction -> Maybe Text
_transactionInvalidHereafter     :: Maybe Text -- ^ Right (excluded) endpoint of the timelock validity intervals
  , Transaction -> Integer
_transactionUtxoCount            :: Integer -- ^ Count of UTXOs within the transaction
  , Transaction -> Integer
_transactionWithdrawalCount      :: Integer -- ^ Count of the withdrawals within the transaction
  , Transaction -> Integer
_transactionMirCertCount         :: Integer -- ^  Count of the MIR certificates within the transaction
  , Transaction -> Integer
_transactionDelegationCount      :: Integer -- ^ Count of the delegations within the transaction
  , Transaction -> Integer
_transactionStakeCertCount       :: Integer -- ^ Count of the stake keys (de)registration and delegation certificates within the transaction
  , Transaction -> Integer
_transactionPoolUpdateCount      :: Integer -- ^ Count of the stake pool registration and update certificates within the transaction
  , Transaction -> Integer
_transactionPoolRetireCount      :: Integer -- ^ Count of the stake pool retirement certificates within the transaction
  , Transaction -> Integer
_transactionAssetMintOrBurnCount :: Integer -- ^ Count of asset mints and burns within the transaction
  , Transaction -> Integer
_transactionRedeemerCount        :: Integer -- ^ Count of redeemers within the transaction
  }
  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
showList :: [Transaction] -> ShowS
$cshowList :: [Transaction] -> ShowS
show :: Transaction -> String
$cshow :: Transaction -> String
showsPrec :: Int -> Transaction -> ShowS
$cshowsPrec :: Int -> Transaction -> ShowS
Show, Transaction -> Transaction -> Bool
(Transaction -> Transaction -> Bool)
-> (Transaction -> Transaction -> Bool) -> Eq Transaction
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. 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
$cto :: forall x. Rep Transaction x -> Transaction
$cfrom :: forall x. Transaction -> Rep Transaction x
Generic)
  deriving (Value -> Parser [Transaction]
Value -> Parser Transaction
(Value -> Parser Transaction)
-> (Value -> Parser [Transaction]) -> FromJSON 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
(Transaction -> Value)
-> (Transaction -> Encoding)
-> ([Transaction] -> Value)
-> ([Transaction] -> Encoding)
-> ToJSON Transaction
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 = [(Text, Transaction)] -> Proxy Transaction -> [(Text, Transaction)]
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 :: Text
-> BlockHash
-> Integer
-> Slot
-> Integer
-> [Amount]
-> Lovelaces
-> Lovelaces
-> Integer
-> Maybe Text
-> Maybe Text
-> Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> Transaction
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 = Lovelaces
182485
      , _transactionDeposit :: Lovelaces
_transactionDeposit = Lovelaces
0
      , _transactionSize :: Integer
_transactionSize = Integer
433
      , _transactionInvalidBefore :: Maybe Text
_transactionInvalidBefore = Maybe Text
forall a. Maybe a
Nothing
      , _transactionInvalidHereafter :: Maybe Text
_transactionInvalidHereafter = Text -> Maybe Text
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
      }

-- | Transaction input UTxO
data UtxoInput = UtxoInput
  { UtxoInput -> Address
_utxoInputAddress     :: Address -- ^ Input address
  , UtxoInput -> [Amount]
_utxoInputAmount      :: [Amount]
  , UtxoInput -> Text
_utxoInputTxHash      :: Text -- ^ Hash of the UTXO transaction
  , UtxoInput -> Integer
_utxoInputOutputIndex :: Integer -- ^ UTXO index in the transaction
  , UtxoInput -> Bool
_utxoInputCollateral  :: Bool -- ^ UTXO is a script collateral input
  , UtxoInput -> Maybe Text
_utxoInputDataHash    :: Maybe Text -- ^ The hash of the transaction output datum
  }
  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
showList :: [UtxoInput] -> ShowS
$cshowList :: [UtxoInput] -> ShowS
show :: UtxoInput -> String
$cshow :: UtxoInput -> String
showsPrec :: Int -> UtxoInput -> ShowS
$cshowsPrec :: Int -> UtxoInput -> ShowS
Show, UtxoInput -> UtxoInput -> Bool
(UtxoInput -> UtxoInput -> Bool)
-> (UtxoInput -> UtxoInput -> Bool) -> Eq UtxoInput
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. 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
$cto :: forall x. Rep UtxoInput x -> UtxoInput
$cfrom :: forall x. UtxoInput -> Rep UtxoInput x
Generic)
  deriving (Value -> Parser [UtxoInput]
Value -> Parser UtxoInput
(Value -> Parser UtxoInput)
-> (Value -> Parser [UtxoInput]) -> FromJSON 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
(UtxoInput -> Value)
-> (UtxoInput -> Encoding)
-> ([UtxoInput] -> Value)
-> ([UtxoInput] -> Encoding)
-> ToJSON UtxoInput
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 = [(Text, UtxoInput)] -> Proxy UtxoInput -> [(Text, UtxoInput)]
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 :: Address
-> [Amount] -> Text -> Integer -> Bool -> Maybe Text -> UtxoInput
UtxoInput
    { _utxoInputAddress :: Address
_utxoInputAddress = Address
"addr1q9ld26v2lv8wvrxxmvg90pn8n8n5k6tdst06q2s856rwmvnueldzuuqmnsye359fqrk8hwvenjnqultn7djtrlft7jnq7dy7wv"
    , _utxoInputAmount :: [Amount]
_utxoInputAmount = [Amount]
sampleAmounts
    , _utxoInputTxHash :: Text
_utxoInputTxHash = Text
"1a0570af966fb355a7160e4f82d5a80b8681b7955f5d44bec0dce628516157f0"
    , _utxoInputOutputIndex :: Integer
_utxoInputOutputIndex = Integer
0
    , _utxoInputCollateral :: Bool
_utxoInputCollateral = Bool
False
    , _utxoInputDataHash :: Maybe Text
_utxoInputDataHash = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"9e478573ab81ea7a8e31891ce0648b81229f408d596a3483e6f4f9b92d3cf710"
    }

-- | Transaction output UTxO
data UtxoOutput = UtxoOutput
  { UtxoOutput -> Address
_utxoOutputAddress     :: Address -- ^ Output address
  , UtxoOutput -> [Amount]
_utxoOutputAmount      :: [Amount] -- ^ Transaction output amounts
  , UtxoOutput -> Maybe Text
_utxoOutputDataHash    :: Maybe Text -- ^ The hash of the transaction output datum
  , UtxoOutput -> Integer
_utxoOutputOutputIndex :: Integer -- ^ UTXO index in the transaction
  } 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
showList :: [UtxoOutput] -> ShowS
$cshowList :: [UtxoOutput] -> ShowS
show :: UtxoOutput -> String
$cshow :: UtxoOutput -> String
showsPrec :: Int -> UtxoOutput -> ShowS
$cshowsPrec :: Int -> UtxoOutput -> ShowS
Show, UtxoOutput -> UtxoOutput -> Bool
(UtxoOutput -> UtxoOutput -> Bool)
-> (UtxoOutput -> UtxoOutput -> Bool) -> Eq UtxoOutput
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. 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
$cto :: forall x. Rep UtxoOutput x -> UtxoOutput
$cfrom :: forall x. UtxoOutput -> Rep UtxoOutput x
Generic)
  deriving (Value -> Parser [UtxoOutput]
Value -> Parser UtxoOutput
(Value -> Parser UtxoOutput)
-> (Value -> Parser [UtxoOutput]) -> FromJSON 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
(UtxoOutput -> Value)
-> (UtxoOutput -> Encoding)
-> ([UtxoOutput] -> Value)
-> ([UtxoOutput] -> Encoding)
-> ToJSON UtxoOutput
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 = [(Text, UtxoOutput)] -> Proxy UtxoOutput -> [(Text, UtxoOutput)]
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 :: Address -> [Amount] -> Maybe Text -> Integer -> UtxoOutput
UtxoOutput
    { _utxoOutputAddress :: Address
_utxoOutputAddress = Address
"addr1q9ld26v2lv8wvrxxmvg90pn8n8n5k6tdst06q2s856rwmvnueldzuuqmnsye359fqrk8hwvenjnqultn7djtrlft7jnq7dy7wv"
    , _utxoOutputAmount :: [Amount]
_utxoOutputAmount = [Amount]
sampleAmounts
    , _utxoOutputDataHash :: Maybe Text
_utxoOutputDataHash = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"9e478573ab81ea7a8e31891ce0648b81229f408d596a3483e6f4f9b92d3cf710"
    , _utxoOutputOutputIndex :: Integer
_utxoOutputOutputIndex = Integer
0
    }

-- | Transaction UTxOs
data TransactionUtxos = TransactionUtxos
  { TransactionUtxos -> TxHash
_transactionUtxosHash    :: TxHash -- ^ Transaction hash
  , TransactionUtxos -> [UtxoInput]
_transactionUtxosInputs  :: [UtxoInput] -- ^ Transaction inputs
  , TransactionUtxos -> [UtxoOutput]
_transactionUtxosOutputs :: [UtxoOutput] -- ^ Transaction outputs
  }
  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
showList :: [TransactionUtxos] -> ShowS
$cshowList :: [TransactionUtxos] -> ShowS
show :: TransactionUtxos -> String
$cshow :: TransactionUtxos -> String
showsPrec :: Int -> TransactionUtxos -> ShowS
$cshowsPrec :: Int -> TransactionUtxos -> ShowS
Show, TransactionUtxos -> TransactionUtxos -> Bool
(TransactionUtxos -> TransactionUtxos -> Bool)
-> (TransactionUtxos -> TransactionUtxos -> Bool)
-> Eq TransactionUtxos
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. 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
$cto :: forall x. Rep TransactionUtxos x -> TransactionUtxos
$cfrom :: forall x. TransactionUtxos -> Rep TransactionUtxos x
Generic)
  deriving (Value -> Parser [TransactionUtxos]
Value -> Parser TransactionUtxos
(Value -> Parser TransactionUtxos)
-> (Value -> Parser [TransactionUtxos])
-> FromJSON 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
(TransactionUtxos -> Value)
-> (TransactionUtxos -> Encoding)
-> ([TransactionUtxos] -> Value)
-> ([TransactionUtxos] -> Encoding)
-> ToJSON TransactionUtxos
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 = [(Text, TransactionUtxos)]
-> Proxy TransactionUtxos -> [(Text, TransactionUtxos)]
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 :: TxHash -> [UtxoInput] -> [UtxoOutput] -> TransactionUtxos
TransactionUtxos
      { _transactionUtxosHash :: TxHash
_transactionUtxosHash = TxHash
"1e043f100dce12d107f679685acd2fc0610e10f72a92d412794c9773d11d8477"
      , _transactionUtxosInputs :: [UtxoInput]
_transactionUtxosInputs = UtxoInput -> [UtxoInput]
forall (f :: * -> *) a. Applicative f => a -> f a
pure UtxoInput
utxoInSample
      , _transactionUtxosOutputs :: [UtxoOutput]
_transactionUtxosOutputs = UtxoOutput -> [UtxoOutput]
forall (f :: * -> *) a. Applicative f => a -> f a
pure UtxoOutput
utxoOutSample
      }

sampleAmounts :: [Amount]
sampleAmounts :: [Amount]
sampleAmounts =
  [ Lovelaces -> Amount
AdaAmount 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
  ]

-- | Validation purpose
data ValidationPurpose = Spend | Mint | Cert | Reward
  deriving stock (Int -> ValidationPurpose -> ShowS
[ValidationPurpose] -> ShowS
ValidationPurpose -> String
(Int -> ValidationPurpose -> ShowS)
-> (ValidationPurpose -> String)
-> ([ValidationPurpose] -> ShowS)
-> Show ValidationPurpose
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ValidationPurpose] -> ShowS
$cshowList :: [ValidationPurpose] -> ShowS
show :: ValidationPurpose -> String
$cshow :: ValidationPurpose -> String
showsPrec :: Int -> ValidationPurpose -> ShowS
$cshowsPrec :: Int -> ValidationPurpose -> ShowS
Show, ValidationPurpose -> ValidationPurpose -> Bool
(ValidationPurpose -> ValidationPurpose -> Bool)
-> (ValidationPurpose -> ValidationPurpose -> Bool)
-> Eq ValidationPurpose
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValidationPurpose -> ValidationPurpose -> Bool
$c/= :: ValidationPurpose -> ValidationPurpose -> Bool
== :: ValidationPurpose -> ValidationPurpose -> Bool
$c== :: ValidationPurpose -> ValidationPurpose -> Bool
Eq, (forall x. ValidationPurpose -> Rep ValidationPurpose x)
-> (forall x. Rep ValidationPurpose x -> ValidationPurpose)
-> Generic ValidationPurpose
forall x. Rep ValidationPurpose x -> ValidationPurpose
forall x. ValidationPurpose -> Rep ValidationPurpose x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ValidationPurpose x -> ValidationPurpose
$cfrom :: forall x. ValidationPurpose -> Rep ValidationPurpose x
Generic)
  deriving (Value -> Parser [ValidationPurpose]
Value -> Parser ValidationPurpose
(Value -> Parser ValidationPurpose)
-> (Value -> Parser [ValidationPurpose])
-> FromJSON ValidationPurpose
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ValidationPurpose]
$cparseJSONList :: Value -> Parser [ValidationPurpose]
parseJSON :: Value -> Parser ValidationPurpose
$cparseJSON :: Value -> Parser ValidationPurpose
FromJSON, [ValidationPurpose] -> Encoding
[ValidationPurpose] -> Value
ValidationPurpose -> Encoding
ValidationPurpose -> Value
(ValidationPurpose -> Value)
-> (ValidationPurpose -> Encoding)
-> ([ValidationPurpose] -> Value)
-> ([ValidationPurpose] -> Encoding)
-> ToJSON ValidationPurpose
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ValidationPurpose] -> Encoding
$ctoEncodingList :: [ValidationPurpose] -> Encoding
toJSONList :: [ValidationPurpose] -> Value
$ctoJSONList :: [ValidationPurpose] -> Value
toEncoding :: ValidationPurpose -> Encoding
$ctoEncoding :: ValidationPurpose -> Encoding
toJSON :: ValidationPurpose -> Value
$ctoJSON :: ValidationPurpose -> Value
ToJSON)
  via CustomJSON '[ConstructorTagModifier '[ToLower]] ValidationPurpose

instance ToSample ValidationPurpose where
  toSamples :: Proxy ValidationPurpose -> [(Text, ValidationPurpose)]
toSamples = [(Text, ValidationPurpose)]
-> Proxy ValidationPurpose -> [(Text, ValidationPurpose)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, ValidationPurpose)]
 -> Proxy ValidationPurpose -> [(Text, ValidationPurpose)])
-> [(Text, ValidationPurpose)]
-> Proxy ValidationPurpose
-> [(Text, ValidationPurpose)]
forall a b. (a -> b) -> a -> b
$ [ValidationPurpose] -> [(Text, ValidationPurpose)]
forall a. [a] -> [(Text, a)]
samples [ ValidationPurpose
Spend, ValidationPurpose
Mint, ValidationPurpose
Cert, ValidationPurpose
Reward ]

-- | Transaction redeemer
data TransactionRedeemer = TransactionRedeemer
  { TransactionRedeemer -> Integer
_transactionRedeemerTxIndex   :: Integer -- ^ Index of the redeemer within a transaction
  , TransactionRedeemer -> ValidationPurpose
_transactionRedeemerPurpose   :: ValidationPurpose -- ^ Validation purpose
  , TransactionRedeemer -> Text
_transactionRedeemerScriptHash:: Text -- ^ Script hash
  , TransactionRedeemer -> Text
_transactionRedeemerDatumHash :: Text -- ^ Datum hash
  , TransactionRedeemer -> Quantity
_transactionRedeemerUnitMem   :: Quantity -- ^ The budget in Memory to run a script
  , TransactionRedeemer -> Quantity
_transactionRedeemerUnitSteps :: Quantity -- ^ The budget in Steps to run a script
  , TransactionRedeemer -> Lovelaces
_transactionRedeemerFee       :: Lovelaces -- ^ The fee consumed to run the script
  }
  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
showList :: [TransactionRedeemer] -> ShowS
$cshowList :: [TransactionRedeemer] -> ShowS
show :: TransactionRedeemer -> String
$cshow :: TransactionRedeemer -> String
showsPrec :: Int -> TransactionRedeemer -> ShowS
$cshowsPrec :: Int -> TransactionRedeemer -> ShowS
Show, TransactionRedeemer -> TransactionRedeemer -> Bool
(TransactionRedeemer -> TransactionRedeemer -> Bool)
-> (TransactionRedeemer -> TransactionRedeemer -> Bool)
-> Eq TransactionRedeemer
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. 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
$cto :: forall x. Rep TransactionRedeemer x -> TransactionRedeemer
$cfrom :: forall x. TransactionRedeemer -> Rep TransactionRedeemer x
Generic)
  deriving (Value -> Parser [TransactionRedeemer]
Value -> Parser TransactionRedeemer
(Value -> Parser TransactionRedeemer)
-> (Value -> Parser [TransactionRedeemer])
-> FromJSON 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
(TransactionRedeemer -> Value)
-> (TransactionRedeemer -> Encoding)
-> ([TransactionRedeemer] -> Value)
-> ([TransactionRedeemer] -> Encoding)
-> ToJSON TransactionRedeemer
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 = [(Text, TransactionRedeemer)]
-> Proxy TransactionRedeemer -> [(Text, TransactionRedeemer)]
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 :: Integer
-> ValidationPurpose
-> Text
-> Text
-> Quantity
-> Quantity
-> Lovelaces
-> TransactionRedeemer
TransactionRedeemer
      { _transactionRedeemerTxIndex :: Integer
_transactionRedeemerTxIndex = Integer
0
      , _transactionRedeemerPurpose :: ValidationPurpose
_transactionRedeemerPurpose = ValidationPurpose
Spend
      , _transactionRedeemerScriptHash :: Text
_transactionRedeemerScriptHash = Text
"ec26b89af41bef0f7585353831cb5da42b5b37185e0c8a526143b824"
      , _transactionRedeemerDatumHash :: Text
_transactionRedeemerDatumHash = Text
"923918e403bf43c34b4ef6b48eb2ee04babed17320d8d1b9ff9ad086e86f44ec"
      , _transactionRedeemerUnitMem :: Quantity
_transactionRedeemerUnitMem = Quantity
1700
      , _transactionRedeemerUnitSteps :: Quantity
_transactionRedeemerUnitSteps = Quantity
476468
      , _transactionRedeemerFee :: Lovelaces
_transactionRedeemerFee = Lovelaces
172033
      }

-- | Information about (de-)registration of a stake address
-- within a transaction
data TransactionStake = TransactionStake
  { TransactionStake -> Integer
_transactionStakeCertIndex    :: Integer -- ^ Index of the certificate within the transaction
  , TransactionStake -> Address
_transactionStakeAddress      :: Address -- ^ Delegation stake address
  , TransactionStake -> Bool
_transactionStakeRegistration :: Bool -- ^ Registration boolean, false if deregistration
  }
  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
showList :: [TransactionStake] -> ShowS
$cshowList :: [TransactionStake] -> ShowS
show :: TransactionStake -> String
$cshow :: TransactionStake -> String
showsPrec :: Int -> TransactionStake -> ShowS
$cshowsPrec :: Int -> TransactionStake -> ShowS
Show, TransactionStake -> TransactionStake -> Bool
(TransactionStake -> TransactionStake -> Bool)
-> (TransactionStake -> TransactionStake -> Bool)
-> Eq TransactionStake
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. 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
$cto :: forall x. Rep TransactionStake x -> TransactionStake
$cfrom :: forall x. TransactionStake -> Rep TransactionStake x
Generic)
  deriving (Value -> Parser [TransactionStake]
Value -> Parser TransactionStake
(Value -> Parser TransactionStake)
-> (Value -> Parser [TransactionStake])
-> FromJSON 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
(TransactionStake -> Value)
-> (TransactionStake -> Encoding)
-> ([TransactionStake] -> Value)
-> ([TransactionStake] -> Encoding)
-> ToJSON TransactionStake
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 = [(Text, TransactionStake)]
-> Proxy TransactionStake -> [(Text, TransactionStake)]
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 :: Integer -> Address -> Bool -> TransactionStake
TransactionStake
      { _transactionStakeCertIndex :: Integer
_transactionStakeCertIndex = Integer
0
      , _transactionStakeAddress :: Address
_transactionStakeAddress = Address
"stake1u9t3a0tcwune5xrnfjg4q7cpvjlgx9lcv0cuqf5mhfjwrvcwrulda"
      , _transactionStakeRegistration :: Bool
_transactionStakeRegistration = Bool
True
      }

-- | Information about delegation certificates of a specific transaction
data TransactionDelegation = TransactionDelegation
  { TransactionDelegation -> Integer
_transactionDelegationCertIndex   :: Integer -- ^ Index of the certificate within the transaction
  , TransactionDelegation -> Address
_transactionDelegationAddress     :: Address -- ^ Delegation stake address
  , TransactionDelegation -> PoolId
_transactionDelegationPoolId      :: PoolId -- ^ Bech32 ID of delegated stake pool
  , TransactionDelegation -> Epoch
_transactionDelegationActiveEpoch :: Epoch -- ^ Epoch in which the delegation becomes active
  }
  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
showList :: [TransactionDelegation] -> ShowS
$cshowList :: [TransactionDelegation] -> ShowS
show :: TransactionDelegation -> String
$cshow :: TransactionDelegation -> String
showsPrec :: Int -> TransactionDelegation -> ShowS
$cshowsPrec :: Int -> TransactionDelegation -> ShowS
Show, TransactionDelegation -> TransactionDelegation -> Bool
(TransactionDelegation -> TransactionDelegation -> Bool)
-> (TransactionDelegation -> TransactionDelegation -> Bool)
-> Eq TransactionDelegation
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. 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
$cto :: forall x. Rep TransactionDelegation x -> TransactionDelegation
$cfrom :: forall x. TransactionDelegation -> Rep TransactionDelegation x
Generic)
  deriving (Value -> Parser [TransactionDelegation]
Value -> Parser TransactionDelegation
(Value -> Parser TransactionDelegation)
-> (Value -> Parser [TransactionDelegation])
-> FromJSON 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
(TransactionDelegation -> Value)
-> (TransactionDelegation -> Encoding)
-> ([TransactionDelegation] -> Value)
-> ([TransactionDelegation] -> Encoding)
-> ToJSON TransactionDelegation
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 = [(Text, TransactionDelegation)]
-> Proxy TransactionDelegation -> [(Text, TransactionDelegation)]
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 :: Integer -> Address -> PoolId -> Epoch -> TransactionDelegation
TransactionDelegation
      { _transactionDelegationCertIndex :: Integer
_transactionDelegationCertIndex = Integer
0
      , _transactionDelegationAddress :: Address
_transactionDelegationAddress = Address
"stake1u9t3a0tcwune5xrnfjg4q7cpvjlgx9lcv0cuqf5mhfjwrvcwrulda"
      , _transactionDelegationPoolId :: PoolId
_transactionDelegationPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
      , _transactionDelegationActiveEpoch :: Epoch
_transactionDelegationActiveEpoch = Epoch
210
      }

-- | Information about withdrawals of a specific transaction
data TransactionWithdrawal = TransactionWithdrawal
  { TransactionWithdrawal -> Address
_transactionWithdrawalAddress :: Address -- ^ Bech32 withdrawal address
  , TransactionWithdrawal -> Lovelaces
_transactionWithdrawalAmount  :: Lovelaces -- ^ Withdrawal amount in 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
showList :: [TransactionWithdrawal] -> ShowS
$cshowList :: [TransactionWithdrawal] -> ShowS
show :: TransactionWithdrawal -> String
$cshow :: TransactionWithdrawal -> String
showsPrec :: Int -> TransactionWithdrawal -> ShowS
$cshowsPrec :: Int -> TransactionWithdrawal -> ShowS
Show, TransactionWithdrawal -> TransactionWithdrawal -> Bool
(TransactionWithdrawal -> TransactionWithdrawal -> Bool)
-> (TransactionWithdrawal -> TransactionWithdrawal -> Bool)
-> Eq TransactionWithdrawal
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. 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
$cto :: forall x. Rep TransactionWithdrawal x -> TransactionWithdrawal
$cfrom :: forall x. TransactionWithdrawal -> Rep TransactionWithdrawal x
Generic)
  deriving (Value -> Parser [TransactionWithdrawal]
Value -> Parser TransactionWithdrawal
(Value -> Parser TransactionWithdrawal)
-> (Value -> Parser [TransactionWithdrawal])
-> FromJSON 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
(TransactionWithdrawal -> Value)
-> (TransactionWithdrawal -> Encoding)
-> ([TransactionWithdrawal] -> Value)
-> ([TransactionWithdrawal] -> Encoding)
-> ToJSON TransactionWithdrawal
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 = [(Text, TransactionWithdrawal)]
-> Proxy TransactionWithdrawal -> [(Text, TransactionWithdrawal)]
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 :: Address -> Lovelaces -> TransactionWithdrawal
TransactionWithdrawal
      { _transactionWithdrawalAddress :: Address
_transactionWithdrawalAddress = Address
"stake1u9r76ypf5fskppa0cmttas05cgcswrttn6jrq4yd7jpdnvc7gt0yc"
      , _transactionWithdrawalAmount :: Lovelaces
_transactionWithdrawalAmount = Lovelaces
431833601
      }

-- | Pot from which MIRs are transferred
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
showList :: [Pot] -> ShowS
$cshowList :: [Pot] -> ShowS
show :: Pot -> String
$cshow :: Pot -> String
showsPrec :: Int -> Pot -> ShowS
$cshowsPrec :: Int -> Pot -> ShowS
Show, Pot -> Pot -> Bool
(Pot -> Pot -> Bool) -> (Pot -> Pot -> Bool) -> Eq Pot
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. 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
$cto :: forall x. Rep Pot x -> Pot
$cfrom :: forall x. Pot -> Rep Pot x
Generic)
  deriving (Value -> Parser [Pot]
Value -> Parser Pot
(Value -> Parser Pot) -> (Value -> Parser [Pot]) -> FromJSON 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
(Pot -> Value)
-> (Pot -> Encoding)
-> ([Pot] -> Value)
-> ([Pot] -> Encoding)
-> ToJSON Pot
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 = [(Text, Pot)] -> Proxy Pot -> [(Text, Pot)]
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 ]

-- | Information about Move Instantaneous Rewards (MIRs) of a specific transaction
data TransactionMir = TransactionMir
  { TransactionMir -> Pot
_transactionMirPot       :: Pot -- ^ Source of MIR funds
  , TransactionMir -> Integer
_transactionMirCertIndex :: Integer -- ^ Index of the certificate within the transaction
  , TransactionMir -> Address
_transactionMirAddress   :: Address -- ^ Bech32 stake address
  , TransactionMir -> Lovelaces
_transactionMirAmount    :: Lovelaces -- ^ MIR amount in 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
showList :: [TransactionMir] -> ShowS
$cshowList :: [TransactionMir] -> ShowS
show :: TransactionMir -> String
$cshow :: TransactionMir -> String
showsPrec :: Int -> TransactionMir -> ShowS
$cshowsPrec :: Int -> TransactionMir -> ShowS
Show, TransactionMir -> TransactionMir -> Bool
(TransactionMir -> TransactionMir -> Bool)
-> (TransactionMir -> TransactionMir -> Bool) -> Eq TransactionMir
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. 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
$cto :: forall x. Rep TransactionMir x -> TransactionMir
$cfrom :: forall x. TransactionMir -> Rep TransactionMir x
Generic)
  deriving (Value -> Parser [TransactionMir]
Value -> Parser TransactionMir
(Value -> Parser TransactionMir)
-> (Value -> Parser [TransactionMir]) -> FromJSON 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
(TransactionMir -> Value)
-> (TransactionMir -> Encoding)
-> ([TransactionMir] -> Value)
-> ([TransactionMir] -> Encoding)
-> ToJSON TransactionMir
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 = [(Text, TransactionMir)]
-> Proxy TransactionMir -> [(Text, TransactionMir)]
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 :: Pot -> Integer -> Address -> Lovelaces -> TransactionMir
TransactionMir
      { _transactionMirPot :: Pot
_transactionMirPot = Pot
Reserve
      , _transactionMirCertIndex :: Integer
_transactionMirCertIndex = Integer
0
      , _transactionMirAddress :: Address
_transactionMirAddress = Address
"stake1u9r76ypf5fskppa0cmttas05cgcswrttn6jrq4yd7jpdnvc7gt0yc"
      , _transactionMirAmount :: Lovelaces
_transactionMirAmount = Lovelaces
431833601
      }

-- | Information about stake pool registration and update certificates
-- of a specific transaction
data TransactionPoolUpdate = TransactionPoolUpdate
  { TransactionPoolUpdate -> Integer
_transactionPoolUpdateCertIndex     :: Integer -- ^ Index of the certificate within the transaction
  , TransactionPoolUpdate -> PoolId
_transactionPoolUpdatePoolId        :: PoolId -- ^ Bech32 encoded pool ID
  , TransactionPoolUpdate -> Text
_transactionPoolUpdateVrfKey        :: Text -- ^ VRF key hash
  , TransactionPoolUpdate -> Lovelaces
_transactionPoolUpdatePledge        :: Lovelaces -- ^ Stake pool certificate pledge in Lovelaces
  , TransactionPoolUpdate -> Double
_transactionPoolUpdateMarginCost    :: Double -- ^  Margin tax cost of the stake pool
  , TransactionPoolUpdate -> Lovelaces
_transactionPoolUpdateFixedCost     :: Lovelaces -- ^ Fixed tax cost of the stake pool in Lovelaces
  , TransactionPoolUpdate -> Address
_transactionPoolUpdateRewardAccount :: Address -- ^ Bech32 reward account of the stake pool
  , TransactionPoolUpdate -> [Address]
_transactionPoolUpdateOwners        :: [Address]
  , TransactionPoolUpdate -> Maybe PoolUpdateMetadata
_transactionPoolUpdateMetadata      ::  Maybe PoolUpdateMetadata
  , TransactionPoolUpdate -> [PoolRelay]
_transactionPoolUpdateRelays        :: [PoolRelay]
  , TransactionPoolUpdate -> Epoch
_transactionPoolUpdateActiveEpoch   :: Epoch -- ^ Epoch that the delegation becomes active
  }
  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
showList :: [TransactionPoolUpdate] -> ShowS
$cshowList :: [TransactionPoolUpdate] -> ShowS
show :: TransactionPoolUpdate -> String
$cshow :: TransactionPoolUpdate -> String
showsPrec :: Int -> TransactionPoolUpdate -> ShowS
$cshowsPrec :: Int -> TransactionPoolUpdate -> ShowS
Show, TransactionPoolUpdate -> TransactionPoolUpdate -> Bool
(TransactionPoolUpdate -> TransactionPoolUpdate -> Bool)
-> (TransactionPoolUpdate -> TransactionPoolUpdate -> Bool)
-> Eq TransactionPoolUpdate
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. 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
$cto :: forall x. Rep TransactionPoolUpdate x -> TransactionPoolUpdate
$cfrom :: forall x. TransactionPoolUpdate -> Rep TransactionPoolUpdate x
Generic)
  deriving (Value -> Parser [TransactionPoolUpdate]
Value -> Parser TransactionPoolUpdate
(Value -> Parser TransactionPoolUpdate)
-> (Value -> Parser [TransactionPoolUpdate])
-> FromJSON 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
(TransactionPoolUpdate -> Value)
-> (TransactionPoolUpdate -> Encoding)
-> ([TransactionPoolUpdate] -> Value)
-> ([TransactionPoolUpdate] -> Encoding)
-> ToJSON TransactionPoolUpdate
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 = [(Text, TransactionPoolUpdate)]
-> Proxy TransactionPoolUpdate -> [(Text, TransactionPoolUpdate)]
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 :: Integer
-> PoolId
-> Text
-> Lovelaces
-> Double
-> Lovelaces
-> Address
-> [Address]
-> Maybe PoolUpdateMetadata
-> [PoolRelay]
-> Epoch
-> TransactionPoolUpdate
TransactionPoolUpdate
      { _transactionPoolUpdateCertIndex :: Integer
_transactionPoolUpdateCertIndex = Integer
0
      , _transactionPoolUpdatePoolId :: PoolId
_transactionPoolUpdatePoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
      , _transactionPoolUpdateVrfKey :: Text
_transactionPoolUpdateVrfKey = Text
"0b5245f9934ec2151116fb8ec00f35fd00e0aa3b075c4ed12cce440f999d8233"
      , _transactionPoolUpdatePledge :: Lovelaces
_transactionPoolUpdatePledge = Lovelaces
5000000000
      , _transactionPoolUpdateMarginCost :: Double
_transactionPoolUpdateMarginCost = Double
0.05
      , _transactionPoolUpdateFixedCost :: Lovelaces
_transactionPoolUpdateFixedCost = Lovelaces
340000000
      , _transactionPoolUpdateRewardAccount :: Address
_transactionPoolUpdateRewardAccount = Address
"stake1uxkptsa4lkr55jleztw43t37vgdn88l6ghclfwuxld2eykgpgvg3f"
      , _transactionPoolUpdateOwners :: [Address]
_transactionPoolUpdateOwners = [ Address
"stake1u98nnlkvkk23vtvf9273uq7cph5ww6u2yq2389psuqet90sv4xv9v" ]
      , _transactionPoolUpdateMetadata :: Maybe PoolUpdateMetadata
_transactionPoolUpdateMetadata = PoolUpdateMetadata -> Maybe PoolUpdateMetadata
forall a. a -> Maybe a
Just PoolUpdateMetadata
samplePoolUpdateMetadata
      , _transactionPoolUpdateRelays :: [PoolRelay]
_transactionPoolUpdateRelays = [ PoolRelay
samplePoolRelay ]
      , _transactionPoolUpdateActiveEpoch :: Epoch
_transactionPoolUpdateActiveEpoch = Epoch
210
      }

-- | Information about stake pool retirements
-- within a specific transaction
data TransactionPoolRetiring = TransactionPoolRetiring
  { TransactionPoolRetiring -> Integer
_transactionPoolRetiringCertIndex     :: Integer -- ^ Index of the certificate within the transaction
  , TransactionPoolRetiring -> PoolId
_transactionPoolRetiringPoolId        :: PoolId -- ^ Bech32 stake pool ID
  , TransactionPoolRetiring -> Epoch
_transactionPoolRetiringRetiringEpoch :: Epoch -- ^ Retiring 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
showList :: [TransactionPoolRetiring] -> ShowS
$cshowList :: [TransactionPoolRetiring] -> ShowS
show :: TransactionPoolRetiring -> String
$cshow :: TransactionPoolRetiring -> String
showsPrec :: Int -> TransactionPoolRetiring -> ShowS
$cshowsPrec :: Int -> TransactionPoolRetiring -> ShowS
Show, TransactionPoolRetiring -> TransactionPoolRetiring -> Bool
(TransactionPoolRetiring -> TransactionPoolRetiring -> Bool)
-> (TransactionPoolRetiring -> TransactionPoolRetiring -> Bool)
-> Eq TransactionPoolRetiring
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.
 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
$cto :: forall x. Rep TransactionPoolRetiring x -> TransactionPoolRetiring
$cfrom :: forall x. TransactionPoolRetiring -> Rep TransactionPoolRetiring x
Generic)
  deriving (Value -> Parser [TransactionPoolRetiring]
Value -> Parser TransactionPoolRetiring
(Value -> Parser TransactionPoolRetiring)
-> (Value -> Parser [TransactionPoolRetiring])
-> FromJSON 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
(TransactionPoolRetiring -> Value)
-> (TransactionPoolRetiring -> Encoding)
-> ([TransactionPoolRetiring] -> Value)
-> ([TransactionPoolRetiring] -> Encoding)
-> ToJSON TransactionPoolRetiring
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 = [(Text, TransactionPoolRetiring)]
-> Proxy TransactionPoolRetiring
-> [(Text, TransactionPoolRetiring)]
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 :: Integer -> PoolId -> Epoch -> TransactionPoolRetiring
TransactionPoolRetiring
      { _transactionPoolRetiringCertIndex :: Integer
_transactionPoolRetiringCertIndex = Integer
0
      , _transactionPoolRetiringPoolId :: PoolId
_transactionPoolRetiringPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
      , _transactionPoolRetiringRetiringEpoch :: Epoch
_transactionPoolRetiringRetiringEpoch = Epoch
216
      }

-- | Transaction metadata in JSON
data TransactionMetaJSON = TransactionMetaJSON
  { TransactionMetaJSON -> Text
_transactionMetaJSONLabel        :: Text -- ^ Metadata label
  , TransactionMetaJSON -> Maybe Value
_transactionMetaJSONJSONMetadata :: Maybe Value -- ^ Content of the JSON metadata
  }
  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
showList :: [TransactionMetaJSON] -> ShowS
$cshowList :: [TransactionMetaJSON] -> ShowS
show :: TransactionMetaJSON -> String
$cshow :: TransactionMetaJSON -> String
showsPrec :: Int -> TransactionMetaJSON -> ShowS
$cshowsPrec :: Int -> TransactionMetaJSON -> ShowS
Show, TransactionMetaJSON -> TransactionMetaJSON -> Bool
(TransactionMetaJSON -> TransactionMetaJSON -> Bool)
-> (TransactionMetaJSON -> TransactionMetaJSON -> Bool)
-> Eq TransactionMetaJSON
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. 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
$cto :: forall x. Rep TransactionMetaJSON x -> TransactionMetaJSON
$cfrom :: forall x. TransactionMetaJSON -> Rep TransactionMetaJSON x
Generic)
  deriving (Value -> Parser [TransactionMetaJSON]
Value -> Parser TransactionMetaJSON
(Value -> Parser TransactionMetaJSON)
-> (Value -> Parser [TransactionMetaJSON])
-> FromJSON 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
(TransactionMetaJSON -> Value)
-> (TransactionMetaJSON -> Encoding)
-> ([TransactionMetaJSON] -> Value)
-> ([TransactionMetaJSON] -> Encoding)
-> ToJSON TransactionMetaJSON
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 [
            Text
"ADAUSD" Text -> [Value] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=
              [ [Pair] -> Value
object [ Text
"value" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
val :: Text)
                       , Text
"source" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"ergoOracles" :: Text) ]
              ]
          ]
    in [(Text, TransactionMetaJSON)]
-> Proxy TransactionMetaJSON -> [(Text, TransactionMetaJSON)]
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
           [ Text
"metadata" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"https://nut.link/metadata.json" :: Text)
           , Text
"hash" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> 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")
    ]

-- | Transaction metadata in CBOR
data TransactionMetaCBOR = TransactionMetaCBOR
  { TransactionMetaCBOR -> Text
_transactionMetaCBORLabel        :: Text -- ^ Metadata label
  , TransactionMetaCBOR -> Maybe Text
_transactionMetaCBORMetadata     :: Maybe Text -- ^ Content of the CBOR metadata
  }
  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
showList :: [TransactionMetaCBOR] -> ShowS
$cshowList :: [TransactionMetaCBOR] -> ShowS
show :: TransactionMetaCBOR -> String
$cshow :: TransactionMetaCBOR -> String
showsPrec :: Int -> TransactionMetaCBOR -> ShowS
$cshowsPrec :: Int -> TransactionMetaCBOR -> ShowS
Show, TransactionMetaCBOR -> TransactionMetaCBOR -> Bool
(TransactionMetaCBOR -> TransactionMetaCBOR -> Bool)
-> (TransactionMetaCBOR -> TransactionMetaCBOR -> Bool)
-> Eq TransactionMetaCBOR
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. 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
$cto :: forall x. Rep TransactionMetaCBOR x -> TransactionMetaCBOR
$cfrom :: forall x. TransactionMetaCBOR -> Rep TransactionMetaCBOR x
Generic)
  deriving (Value -> Parser [TransactionMetaCBOR]
Value -> Parser TransactionMetaCBOR
(Value -> Parser TransactionMetaCBOR)
-> (Value -> Parser [TransactionMetaCBOR])
-> FromJSON 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
(TransactionMetaCBOR -> Value)
-> (TransactionMetaCBOR -> Encoding)
-> ([TransactionMetaCBOR] -> Value)
-> ([TransactionMetaCBOR] -> Encoding)
-> ToJSON TransactionMetaCBOR
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 = [(Text, TransactionMetaCBOR)]
-> Proxy TransactionMetaCBOR -> [(Text, TransactionMetaCBOR)]
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")

-- | Update of a pool metadata
data PoolUpdateMetadata = PoolUpdateMetadata
  { PoolUpdateMetadata -> Maybe Text
_poolUpdateMetadataUrl         :: Maybe Text -- ^ URL to the stake pool metadata
  , PoolUpdateMetadata -> Maybe Text
_poolUpdateMetadataHash        :: Maybe Text -- ^ Hash of the metadata file
  , PoolUpdateMetadata -> Maybe Text
_poolUpdateMetadataTicker      :: Maybe Text -- ^ Ticker of the stake pool
  , PoolUpdateMetadata -> Maybe Text
_poolUpdateMetadataName        :: Maybe Text -- ^ Name of the stake pool
  , PoolUpdateMetadata -> Maybe Text
_poolUpdateMetadataDescription :: Maybe Text -- ^ Description of the stake pool
  , PoolUpdateMetadata -> Maybe Text
_poolUpdateMetadataHomepage    :: Maybe Text -- ^ Home page of the stake pool
  }
  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
showList :: [PoolUpdateMetadata] -> ShowS
$cshowList :: [PoolUpdateMetadata] -> ShowS
show :: PoolUpdateMetadata -> String
$cshow :: PoolUpdateMetadata -> String
showsPrec :: Int -> PoolUpdateMetadata -> ShowS
$cshowsPrec :: Int -> PoolUpdateMetadata -> ShowS
Show, PoolUpdateMetadata -> PoolUpdateMetadata -> Bool
(PoolUpdateMetadata -> PoolUpdateMetadata -> Bool)
-> (PoolUpdateMetadata -> PoolUpdateMetadata -> Bool)
-> Eq PoolUpdateMetadata
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. 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
$cto :: forall x. Rep PoolUpdateMetadata x -> PoolUpdateMetadata
$cfrom :: forall x. PoolUpdateMetadata -> Rep PoolUpdateMetadata x
Generic)
  deriving (Value -> Parser [PoolUpdateMetadata]
Value -> Parser PoolUpdateMetadata
(Value -> Parser PoolUpdateMetadata)
-> (Value -> Parser [PoolUpdateMetadata])
-> FromJSON 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
(PoolUpdateMetadata -> Value)
-> (PoolUpdateMetadata -> Encoding)
-> ([PoolUpdateMetadata] -> Value)
-> ([PoolUpdateMetadata] -> Encoding)
-> ToJSON PoolUpdateMetadata
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

-- Note: Similar to PoolMetadata but w/o PoolId and Hex fields

instance ToSample PoolUpdateMetadata where
  toSamples :: Proxy PoolUpdateMetadata -> [(Text, PoolUpdateMetadata)]
toSamples = [(Text, PoolUpdateMetadata)]
-> Proxy PoolUpdateMetadata -> [(Text, PoolUpdateMetadata)]
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 :: Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PoolUpdateMetadata
PoolUpdateMetadata
    { _poolUpdateMetadataUrl :: Maybe Text
_poolUpdateMetadataUrl = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"https://stakenuts.com/mainnet.json"
    , _poolUpdateMetadataHash :: Maybe Text
_poolUpdateMetadataHash = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"47c0c68cb57f4a5b4a87bad896fc274678e7aea98e200fa14a1cb40c0cab1d8c"
    , _poolUpdateMetadataTicker :: Maybe Text
_poolUpdateMetadataTicker = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"NUTS"
    , _poolUpdateMetadataName :: Maybe Text
_poolUpdateMetadataName = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"Stake Nuts"
    , _poolUpdateMetadataDescription :: Maybe Text
_poolUpdateMetadataDescription = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"The best pool ever"
    , _poolUpdateMetadataHomepage :: Maybe Text
_poolUpdateMetadataHomepage = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"https://stakentus.com/"
    }