-- | Responses for Cardano accounts queries

module Blockfrost.Types.Cardano.Accounts
  ( AccountInfo (..)
  , AccountReward (..)
  , AccountHistory (..)
  , AccountDelegation (..)
  , AccountRegistration (..)
  , AccountRegistrationAction (..)
  , AccountWithdrawal (..)
  , AccountMir (..)
  , AddressAssociated (..)
  ) where

import Blockfrost.Types.Shared
import Deriving.Aeson
import Servant.Docs (ToSample (..), samples, singleSample)

-- | Information about an account, identified by its stake address
data AccountInfo = AccountInfo
  { AccountInfo -> Address
_accountInfoStakeAddress       :: Address -- ^ Bech32 stake address
  , AccountInfo -> Bool
_accountInfoActive             :: Bool -- ^ Registration state of an account
  , AccountInfo -> Integer
_accountInfoActiveEpoch        :: Integer -- ^ Epoch of the most recent action - registration or deregistration
  , AccountInfo -> Lovelaces
_accountInfoControlledAmount   :: Lovelaces  -- ^ Balance of the account in Lovelaces
  , AccountInfo -> Lovelaces
_accountInfoRewardsSum         :: Lovelaces -- ^ Sum of all funds rewards for the account in the Lovelaces
  , AccountInfo -> Lovelaces
_accountInfoWithdrawalsSum     :: Lovelaces -- ^ Sum of all the withdrawals for the account in the Lovelaces
  , AccountInfo -> Lovelaces
_accountInfoReservesSum        :: Lovelaces -- ^ Sum of all funds from reserves for the account in the Lovelaces
  , AccountInfo -> Lovelaces
_accountInfoTreasurySum        :: Lovelaces -- ^ Sum of all funds from treasury for the account in the Lovelaces
  , AccountInfo -> Lovelaces
_accountInfoWithdrawableAmount :: Lovelaces -- ^ Sum of available rewards that haven't been withdrawn yet for the account in the Lovelaces
  , AccountInfo -> Maybe PoolId
_accountInfoPoolId             :: Maybe PoolId -- ^ Bech32 pool ID that owns the account
  }
  deriving stock (Int -> AccountInfo -> ShowS
[AccountInfo] -> ShowS
AccountInfo -> String
(Int -> AccountInfo -> ShowS)
-> (AccountInfo -> String)
-> ([AccountInfo] -> ShowS)
-> Show AccountInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountInfo] -> ShowS
$cshowList :: [AccountInfo] -> ShowS
show :: AccountInfo -> String
$cshow :: AccountInfo -> String
showsPrec :: Int -> AccountInfo -> ShowS
$cshowsPrec :: Int -> AccountInfo -> ShowS
Show, AccountInfo -> AccountInfo -> Bool
(AccountInfo -> AccountInfo -> Bool)
-> (AccountInfo -> AccountInfo -> Bool) -> Eq AccountInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountInfo -> AccountInfo -> Bool
$c/= :: AccountInfo -> AccountInfo -> Bool
== :: AccountInfo -> AccountInfo -> Bool
$c== :: AccountInfo -> AccountInfo -> Bool
Eq, (forall x. AccountInfo -> Rep AccountInfo x)
-> (forall x. Rep AccountInfo x -> AccountInfo)
-> Generic AccountInfo
forall x. Rep AccountInfo x -> AccountInfo
forall x. AccountInfo -> Rep AccountInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountInfo x -> AccountInfo
$cfrom :: forall x. AccountInfo -> Rep AccountInfo x
Generic)
  deriving (Value -> Parser [AccountInfo]
Value -> Parser AccountInfo
(Value -> Parser AccountInfo)
-> (Value -> Parser [AccountInfo]) -> FromJSON AccountInfo
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AccountInfo]
$cparseJSONList :: Value -> Parser [AccountInfo]
parseJSON :: Value -> Parser AccountInfo
$cparseJSON :: Value -> Parser AccountInfo
FromJSON, [AccountInfo] -> Encoding
[AccountInfo] -> Value
AccountInfo -> Encoding
AccountInfo -> Value
(AccountInfo -> Value)
-> (AccountInfo -> Encoding)
-> ([AccountInfo] -> Value)
-> ([AccountInfo] -> Encoding)
-> ToJSON AccountInfo
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AccountInfo] -> Encoding
$ctoEncodingList :: [AccountInfo] -> Encoding
toJSONList :: [AccountInfo] -> Value
$ctoJSONList :: [AccountInfo] -> Value
toEncoding :: AccountInfo -> Encoding
$ctoEncoding :: AccountInfo -> Encoding
toJSON :: AccountInfo -> Value
$ctoJSON :: AccountInfo -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountInfo", CamelToSnake]] AccountInfo

instance ToSample AccountInfo where
  toSamples :: Proxy AccountInfo -> [(Text, AccountInfo)]
toSamples = [(Text, AccountInfo)] -> Proxy AccountInfo -> [(Text, AccountInfo)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountInfo)]
 -> Proxy AccountInfo -> [(Text, AccountInfo)])
-> [(Text, AccountInfo)]
-> Proxy AccountInfo
-> [(Text, AccountInfo)]
forall a b. (a -> b) -> a -> b
$ AccountInfo -> [(Text, AccountInfo)]
forall a. a -> [(Text, a)]
singleSample (AccountInfo -> [(Text, AccountInfo)])
-> AccountInfo -> [(Text, AccountInfo)]
forall a b. (a -> b) -> a -> b
$ AccountInfo :: Address
-> Bool
-> Integer
-> Lovelaces
-> Lovelaces
-> Lovelaces
-> Lovelaces
-> Lovelaces
-> Lovelaces
-> Maybe PoolId
-> AccountInfo
AccountInfo
    { _accountInfoStakeAddress :: Address
_accountInfoStakeAddress = Address
"stake1ux3g2c9dx2nhhehyrezyxpkstartcqmu9hk63qgfkccw5rqttygt7"
    , _accountInfoActive :: Bool
_accountInfoActive = Bool
True
    , _accountInfoActiveEpoch :: Integer
_accountInfoActiveEpoch = Integer
412
    , _accountInfoControlledAmount :: Lovelaces
_accountInfoControlledAmount = Lovelaces
619154618165
    , _accountInfoRewardsSum :: Lovelaces
_accountInfoRewardsSum = Lovelaces
319154618165
    , _accountInfoWithdrawalsSum :: Lovelaces
_accountInfoWithdrawalsSum = Lovelaces
12125369253
    , _accountInfoReservesSum :: Lovelaces
_accountInfoReservesSum = Lovelaces
319154618165
    , _accountInfoTreasurySum :: Lovelaces
_accountInfoTreasurySum = Lovelaces
12000000
    , _accountInfoWithdrawableAmount :: Lovelaces
_accountInfoWithdrawableAmount = Lovelaces
319154618165
    , _accountInfoPoolId :: Maybe PoolId
_accountInfoPoolId = PoolId -> Maybe PoolId
forall (f :: * -> *) a. Applicative f => a -> f a
pure PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
    }

-- | Reward received by an account
data AccountReward = AccountReward
  { AccountReward -> Epoch
_accountRewardEpoch  :: Epoch -- ^ Epoch of the associated reward
  , AccountReward -> Lovelaces
_accountRewardAmount :: Lovelaces -- ^ Rewards for given epoch in Lovelaces
  , AccountReward -> PoolId
_accountRewardPoolId :: PoolId -- ^ Bech32 pool ID being delegated to
  }
  deriving stock (Int -> AccountReward -> ShowS
[AccountReward] -> ShowS
AccountReward -> String
(Int -> AccountReward -> ShowS)
-> (AccountReward -> String)
-> ([AccountReward] -> ShowS)
-> Show AccountReward
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountReward] -> ShowS
$cshowList :: [AccountReward] -> ShowS
show :: AccountReward -> String
$cshow :: AccountReward -> String
showsPrec :: Int -> AccountReward -> ShowS
$cshowsPrec :: Int -> AccountReward -> ShowS
Show, AccountReward -> AccountReward -> Bool
(AccountReward -> AccountReward -> Bool)
-> (AccountReward -> AccountReward -> Bool) -> Eq AccountReward
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountReward -> AccountReward -> Bool
$c/= :: AccountReward -> AccountReward -> Bool
== :: AccountReward -> AccountReward -> Bool
$c== :: AccountReward -> AccountReward -> Bool
Eq, (forall x. AccountReward -> Rep AccountReward x)
-> (forall x. Rep AccountReward x -> AccountReward)
-> Generic AccountReward
forall x. Rep AccountReward x -> AccountReward
forall x. AccountReward -> Rep AccountReward x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountReward x -> AccountReward
$cfrom :: forall x. AccountReward -> Rep AccountReward x
Generic)
  deriving (Value -> Parser [AccountReward]
Value -> Parser AccountReward
(Value -> Parser AccountReward)
-> (Value -> Parser [AccountReward]) -> FromJSON AccountReward
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AccountReward]
$cparseJSONList :: Value -> Parser [AccountReward]
parseJSON :: Value -> Parser AccountReward
$cparseJSON :: Value -> Parser AccountReward
FromJSON, [AccountReward] -> Encoding
[AccountReward] -> Value
AccountReward -> Encoding
AccountReward -> Value
(AccountReward -> Value)
-> (AccountReward -> Encoding)
-> ([AccountReward] -> Value)
-> ([AccountReward] -> Encoding)
-> ToJSON AccountReward
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AccountReward] -> Encoding
$ctoEncodingList :: [AccountReward] -> Encoding
toJSONList :: [AccountReward] -> Value
$ctoJSONList :: [AccountReward] -> Value
toEncoding :: AccountReward -> Encoding
$ctoEncoding :: AccountReward -> Encoding
toJSON :: AccountReward -> Value
$ctoJSON :: AccountReward -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountReward", CamelToSnake]] AccountReward

instance ToSample AccountReward where
  toSamples :: Proxy AccountReward -> [(Text, AccountReward)]
toSamples = [(Text, AccountReward)]
-> Proxy AccountReward -> [(Text, AccountReward)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountReward)]
 -> Proxy AccountReward -> [(Text, AccountReward)])
-> [(Text, AccountReward)]
-> Proxy AccountReward
-> [(Text, AccountReward)]
forall a b. (a -> b) -> a -> b
$ [AccountReward] -> [(Text, AccountReward)]
forall a. [a] -> [(Text, a)]
samples
    [ AccountReward :: Epoch -> Lovelaces -> PoolId -> AccountReward
AccountReward
        { _accountRewardEpoch :: Epoch
_accountRewardEpoch = Epoch
214
        , _accountRewardAmount :: Lovelaces
_accountRewardAmount = Lovelaces
1395265
        , _accountRewardPoolId :: PoolId
_accountRewardPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        }
    , AccountReward :: Epoch -> Lovelaces -> PoolId -> AccountReward
AccountReward
        { _accountRewardEpoch :: Epoch
_accountRewardEpoch = Epoch
215
        , _accountRewardAmount :: Lovelaces
_accountRewardAmount = Lovelaces
58632
        , _accountRewardPoolId :: PoolId
_accountRewardPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        }
    , AccountReward :: Epoch -> Lovelaces -> PoolId -> AccountReward
AccountReward
        { _accountRewardEpoch :: Epoch
_accountRewardEpoch = Epoch
216
        , _accountRewardAmount :: Lovelaces
_accountRewardAmount = Lovelaces
0
        , _accountRewardPoolId :: PoolId
_accountRewardPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        }
    , AccountReward :: Epoch -> Lovelaces -> PoolId -> AccountReward
AccountReward
        { _accountRewardEpoch :: Epoch
_accountRewardEpoch = Epoch
217
        , _accountRewardAmount :: Lovelaces
_accountRewardAmount = Lovelaces
1395265
        , _accountRewardPoolId :: PoolId
_accountRewardPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        }
    ]

-- | History of accounts stake delegation
data AccountHistory = AccountHistory
  { AccountHistory -> Integer
_accountHistoryActiveEpoch :: Integer -- ^ Epoch in which the stake was active
  , AccountHistory -> Lovelaces
_accountHistoryAmount      :: Lovelaces -- ^ Stake amount in Lovelaces
  , AccountHistory -> PoolId
_accountHistoryPoolId      :: PoolId -- ^ Bech32 ID of pool being delegated to
  }
  deriving stock (Int -> AccountHistory -> ShowS
[AccountHistory] -> ShowS
AccountHistory -> String
(Int -> AccountHistory -> ShowS)
-> (AccountHistory -> String)
-> ([AccountHistory] -> ShowS)
-> Show AccountHistory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountHistory] -> ShowS
$cshowList :: [AccountHistory] -> ShowS
show :: AccountHistory -> String
$cshow :: AccountHistory -> String
showsPrec :: Int -> AccountHistory -> ShowS
$cshowsPrec :: Int -> AccountHistory -> ShowS
Show, AccountHistory -> AccountHistory -> Bool
(AccountHistory -> AccountHistory -> Bool)
-> (AccountHistory -> AccountHistory -> Bool) -> Eq AccountHistory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountHistory -> AccountHistory -> Bool
$c/= :: AccountHistory -> AccountHistory -> Bool
== :: AccountHistory -> AccountHistory -> Bool
$c== :: AccountHistory -> AccountHistory -> Bool
Eq, (forall x. AccountHistory -> Rep AccountHistory x)
-> (forall x. Rep AccountHistory x -> AccountHistory)
-> Generic AccountHistory
forall x. Rep AccountHistory x -> AccountHistory
forall x. AccountHistory -> Rep AccountHistory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountHistory x -> AccountHistory
$cfrom :: forall x. AccountHistory -> Rep AccountHistory x
Generic)
  deriving (Value -> Parser [AccountHistory]
Value -> Parser AccountHistory
(Value -> Parser AccountHistory)
-> (Value -> Parser [AccountHistory]) -> FromJSON AccountHistory
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AccountHistory]
$cparseJSONList :: Value -> Parser [AccountHistory]
parseJSON :: Value -> Parser AccountHistory
$cparseJSON :: Value -> Parser AccountHistory
FromJSON, [AccountHistory] -> Encoding
[AccountHistory] -> Value
AccountHistory -> Encoding
AccountHistory -> Value
(AccountHistory -> Value)
-> (AccountHistory -> Encoding)
-> ([AccountHistory] -> Value)
-> ([AccountHistory] -> Encoding)
-> ToJSON AccountHistory
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AccountHistory] -> Encoding
$ctoEncodingList :: [AccountHistory] -> Encoding
toJSONList :: [AccountHistory] -> Value
$ctoJSONList :: [AccountHistory] -> Value
toEncoding :: AccountHistory -> Encoding
$ctoEncoding :: AccountHistory -> Encoding
toJSON :: AccountHistory -> Value
$ctoJSON :: AccountHistory -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountHistory", CamelToSnake]] AccountHistory

instance ToSample AccountHistory where
  toSamples :: Proxy AccountHistory -> [(Text, AccountHistory)]
toSamples  = [(Text, AccountHistory)]
-> Proxy AccountHistory -> [(Text, AccountHistory)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountHistory)]
 -> Proxy AccountHistory -> [(Text, AccountHistory)])
-> [(Text, AccountHistory)]
-> Proxy AccountHistory
-> [(Text, AccountHistory)]
forall a b. (a -> b) -> a -> b
$ [AccountHistory] -> [(Text, AccountHistory)]
forall a. [a] -> [(Text, a)]
samples
    [ AccountHistory :: Integer -> Lovelaces -> PoolId -> AccountHistory
AccountHistory
        { _accountHistoryActiveEpoch :: Integer
_accountHistoryActiveEpoch = Integer
260
        , _accountHistoryAmount :: Lovelaces
_accountHistoryAmount = Lovelaces
1395265
        , _accountHistoryPoolId :: PoolId
_accountHistoryPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        }
    , AccountHistory :: Integer -> Lovelaces -> PoolId -> AccountHistory
AccountHistory
        { _accountHistoryActiveEpoch :: Integer
_accountHistoryActiveEpoch = Integer
211
        , _accountHistoryAmount :: Lovelaces
_accountHistoryAmount = Lovelaces
22695385
        , _accountHistoryPoolId :: PoolId
_accountHistoryPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        }
    ]

-- | Account delegations and associated transaction IDs
data AccountDelegation = AccountDelegation
  { AccountDelegation -> Epoch
_accountDelegationActiveEpoch :: Epoch -- ^ Epoch in which the delegation becomes active
  , AccountDelegation -> TxHash
_accountDelegationTxHash      :: TxHash -- ^ Hash of the transaction containing the delegation
  , AccountDelegation -> Lovelaces
_accountDelegationAmount      :: Lovelaces -- ^ Rewards for given epoch in Lovelaces
  , AccountDelegation -> PoolId
_accountDelegationPoolId      :: PoolId -- ^ Bech32 ID of pool being delegated to
  }
  deriving stock (Int -> AccountDelegation -> ShowS
[AccountDelegation] -> ShowS
AccountDelegation -> String
(Int -> AccountDelegation -> ShowS)
-> (AccountDelegation -> String)
-> ([AccountDelegation] -> ShowS)
-> Show AccountDelegation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountDelegation] -> ShowS
$cshowList :: [AccountDelegation] -> ShowS
show :: AccountDelegation -> String
$cshow :: AccountDelegation -> String
showsPrec :: Int -> AccountDelegation -> ShowS
$cshowsPrec :: Int -> AccountDelegation -> ShowS
Show, AccountDelegation -> AccountDelegation -> Bool
(AccountDelegation -> AccountDelegation -> Bool)
-> (AccountDelegation -> AccountDelegation -> Bool)
-> Eq AccountDelegation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountDelegation -> AccountDelegation -> Bool
$c/= :: AccountDelegation -> AccountDelegation -> Bool
== :: AccountDelegation -> AccountDelegation -> Bool
$c== :: AccountDelegation -> AccountDelegation -> Bool
Eq, (forall x. AccountDelegation -> Rep AccountDelegation x)
-> (forall x. Rep AccountDelegation x -> AccountDelegation)
-> Generic AccountDelegation
forall x. Rep AccountDelegation x -> AccountDelegation
forall x. AccountDelegation -> Rep AccountDelegation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountDelegation x -> AccountDelegation
$cfrom :: forall x. AccountDelegation -> Rep AccountDelegation x
Generic)
  deriving (Value -> Parser [AccountDelegation]
Value -> Parser AccountDelegation
(Value -> Parser AccountDelegation)
-> (Value -> Parser [AccountDelegation])
-> FromJSON AccountDelegation
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AccountDelegation]
$cparseJSONList :: Value -> Parser [AccountDelegation]
parseJSON :: Value -> Parser AccountDelegation
$cparseJSON :: Value -> Parser AccountDelegation
FromJSON, [AccountDelegation] -> Encoding
[AccountDelegation] -> Value
AccountDelegation -> Encoding
AccountDelegation -> Value
(AccountDelegation -> Value)
-> (AccountDelegation -> Encoding)
-> ([AccountDelegation] -> Value)
-> ([AccountDelegation] -> Encoding)
-> ToJSON AccountDelegation
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AccountDelegation] -> Encoding
$ctoEncodingList :: [AccountDelegation] -> Encoding
toJSONList :: [AccountDelegation] -> Value
$ctoJSONList :: [AccountDelegation] -> Value
toEncoding :: AccountDelegation -> Encoding
$ctoEncoding :: AccountDelegation -> Encoding
toJSON :: AccountDelegation -> Value
$ctoJSON :: AccountDelegation -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountDelegation", CamelToSnake]] AccountDelegation

instance ToSample AccountDelegation where
  toSamples :: Proxy AccountDelegation -> [(Text, AccountDelegation)]
toSamples = [(Text, AccountDelegation)]
-> Proxy AccountDelegation -> [(Text, AccountDelegation)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountDelegation)]
 -> Proxy AccountDelegation -> [(Text, AccountDelegation)])
-> [(Text, AccountDelegation)]
-> Proxy AccountDelegation
-> [(Text, AccountDelegation)]
forall a b. (a -> b) -> a -> b
$ [AccountDelegation] -> [(Text, AccountDelegation)]
forall a. [a] -> [(Text, a)]
samples
    [ AccountDelegation :: Epoch -> TxHash -> Lovelaces -> PoolId -> AccountDelegation
AccountDelegation
        { _accountDelegationActiveEpoch :: Epoch
_accountDelegationActiveEpoch = Epoch
210
        , _accountDelegationTxHash :: TxHash
_accountDelegationTxHash = TxHash
"2dd15e0ef6e6a17841cb9541c27724072ce4d4b79b91e58432fbaa32d9572531"
        , _accountDelegationAmount :: Lovelaces
_accountDelegationAmount = Lovelaces
12695385
        , _accountDelegationPoolId :: PoolId
_accountDelegationPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        }
    , AccountDelegation :: Epoch -> TxHash -> Lovelaces -> PoolId -> AccountDelegation
AccountDelegation
        { _accountDelegationActiveEpoch :: Epoch
_accountDelegationActiveEpoch = Epoch
242
        , _accountDelegationTxHash :: TxHash
_accountDelegationTxHash = TxHash
"1a0570af966fb355a7160e4f82d5a80b8681b7955f5d44bec0dde628516157f0"
        , _accountDelegationAmount :: Lovelaces
_accountDelegationAmount = Lovelaces
12691385
        , _accountDelegationPoolId :: PoolId
_accountDelegationPoolId = PoolId
"pool1kchver88u3kygsak8wgll7htr8uxn5v35lfrsyy842nkscrzyvj"
        }
    ]

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

instance ToSample AccountRegistrationAction where
  toSamples :: Proxy AccountRegistrationAction
-> [(Text, AccountRegistrationAction)]
toSamples = [(Text, AccountRegistrationAction)]
-> Proxy AccountRegistrationAction
-> [(Text, AccountRegistrationAction)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountRegistrationAction)]
 -> Proxy AccountRegistrationAction
 -> [(Text, AccountRegistrationAction)])
-> [(Text, AccountRegistrationAction)]
-> Proxy AccountRegistrationAction
-> [(Text, AccountRegistrationAction)]
forall a b. (a -> b) -> a -> b
$ [AccountRegistrationAction] -> [(Text, AccountRegistrationAction)]
forall a. [a] -> [(Text, a)]
samples [ AccountRegistrationAction
Registered, AccountRegistrationAction
Deregistered ]

-- | Account (de)registration
data AccountRegistration = AccountRegistration
  { AccountRegistration -> AccountRegistrationAction
_accountRegistrationAction :: AccountRegistrationAction -- ^ Action in the certificate
  , AccountRegistration -> TxHash
_accountRegistrationTxHash :: TxHash -- ^ Hash of the transaction containing the (de)registration certificate
  }
  deriving stock (Int -> AccountRegistration -> ShowS
[AccountRegistration] -> ShowS
AccountRegistration -> String
(Int -> AccountRegistration -> ShowS)
-> (AccountRegistration -> String)
-> ([AccountRegistration] -> ShowS)
-> Show AccountRegistration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountRegistration] -> ShowS
$cshowList :: [AccountRegistration] -> ShowS
show :: AccountRegistration -> String
$cshow :: AccountRegistration -> String
showsPrec :: Int -> AccountRegistration -> ShowS
$cshowsPrec :: Int -> AccountRegistration -> ShowS
Show, AccountRegistration -> AccountRegistration -> Bool
(AccountRegistration -> AccountRegistration -> Bool)
-> (AccountRegistration -> AccountRegistration -> Bool)
-> Eq AccountRegistration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountRegistration -> AccountRegistration -> Bool
$c/= :: AccountRegistration -> AccountRegistration -> Bool
== :: AccountRegistration -> AccountRegistration -> Bool
$c== :: AccountRegistration -> AccountRegistration -> Bool
Eq, (forall x. AccountRegistration -> Rep AccountRegistration x)
-> (forall x. Rep AccountRegistration x -> AccountRegistration)
-> Generic AccountRegistration
forall x. Rep AccountRegistration x -> AccountRegistration
forall x. AccountRegistration -> Rep AccountRegistration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountRegistration x -> AccountRegistration
$cfrom :: forall x. AccountRegistration -> Rep AccountRegistration x
Generic)
  deriving (Value -> Parser [AccountRegistration]
Value -> Parser AccountRegistration
(Value -> Parser AccountRegistration)
-> (Value -> Parser [AccountRegistration])
-> FromJSON AccountRegistration
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AccountRegistration]
$cparseJSONList :: Value -> Parser [AccountRegistration]
parseJSON :: Value -> Parser AccountRegistration
$cparseJSON :: Value -> Parser AccountRegistration
FromJSON, [AccountRegistration] -> Encoding
[AccountRegistration] -> Value
AccountRegistration -> Encoding
AccountRegistration -> Value
(AccountRegistration -> Value)
-> (AccountRegistration -> Encoding)
-> ([AccountRegistration] -> Value)
-> ([AccountRegistration] -> Encoding)
-> ToJSON AccountRegistration
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AccountRegistration] -> Encoding
$ctoEncodingList :: [AccountRegistration] -> Encoding
toJSONList :: [AccountRegistration] -> Value
$ctoJSONList :: [AccountRegistration] -> Value
toEncoding :: AccountRegistration -> Encoding
$ctoEncoding :: AccountRegistration -> Encoding
toJSON :: AccountRegistration -> Value
$ctoJSON :: AccountRegistration -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountRegistration", CamelToSnake]] AccountRegistration

instance ToSample AccountRegistration where
  toSamples :: Proxy AccountRegistration -> [(Text, AccountRegistration)]
toSamples = [(Text, AccountRegistration)]
-> Proxy AccountRegistration -> [(Text, AccountRegistration)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountRegistration)]
 -> Proxy AccountRegistration -> [(Text, AccountRegistration)])
-> [(Text, AccountRegistration)]
-> Proxy AccountRegistration
-> [(Text, AccountRegistration)]
forall a b. (a -> b) -> a -> b
$ [AccountRegistration] -> [(Text, AccountRegistration)]
forall a. [a] -> [(Text, a)]
samples
    [ AccountRegistration :: AccountRegistrationAction -> TxHash -> AccountRegistration
AccountRegistration
        { _accountRegistrationAction :: AccountRegistrationAction
_accountRegistrationAction = AccountRegistrationAction
Registered
        , _accountRegistrationTxHash :: TxHash
_accountRegistrationTxHash = TxHash
"2dd15e0ef6e6a17841cb9541c27724072ce4d4b79b91e58432fbaa32d9572531"
        }
    , AccountRegistration :: AccountRegistrationAction -> TxHash -> AccountRegistration
AccountRegistration
        { _accountRegistrationAction :: AccountRegistrationAction
_accountRegistrationAction = AccountRegistrationAction
Deregistered
        , _accountRegistrationTxHash :: TxHash
_accountRegistrationTxHash = TxHash
"1a0570af966fb355a7160e4f82d5a80b8681b7955f5d44bec0dde628516157f0"
        }
    ]

-- | Withdrawal from an account
data AccountWithdrawal = AccountWithdrawal
  { AccountWithdrawal -> Lovelaces
_accountWithdrawalAmount :: Lovelaces -- ^ Withdrawal amount in Lovelaces
  , AccountWithdrawal -> TxHash
_accountWithdrawalTxHash :: TxHash -- ^ Hash of the transaction containing the withdrawal
  }
  deriving stock (Int -> AccountWithdrawal -> ShowS
[AccountWithdrawal] -> ShowS
AccountWithdrawal -> String
(Int -> AccountWithdrawal -> ShowS)
-> (AccountWithdrawal -> String)
-> ([AccountWithdrawal] -> ShowS)
-> Show AccountWithdrawal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountWithdrawal] -> ShowS
$cshowList :: [AccountWithdrawal] -> ShowS
show :: AccountWithdrawal -> String
$cshow :: AccountWithdrawal -> String
showsPrec :: Int -> AccountWithdrawal -> ShowS
$cshowsPrec :: Int -> AccountWithdrawal -> ShowS
Show, AccountWithdrawal -> AccountWithdrawal -> Bool
(AccountWithdrawal -> AccountWithdrawal -> Bool)
-> (AccountWithdrawal -> AccountWithdrawal -> Bool)
-> Eq AccountWithdrawal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountWithdrawal -> AccountWithdrawal -> Bool
$c/= :: AccountWithdrawal -> AccountWithdrawal -> Bool
== :: AccountWithdrawal -> AccountWithdrawal -> Bool
$c== :: AccountWithdrawal -> AccountWithdrawal -> Bool
Eq, (forall x. AccountWithdrawal -> Rep AccountWithdrawal x)
-> (forall x. Rep AccountWithdrawal x -> AccountWithdrawal)
-> Generic AccountWithdrawal
forall x. Rep AccountWithdrawal x -> AccountWithdrawal
forall x. AccountWithdrawal -> Rep AccountWithdrawal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountWithdrawal x -> AccountWithdrawal
$cfrom :: forall x. AccountWithdrawal -> Rep AccountWithdrawal x
Generic)
  deriving (Value -> Parser [AccountWithdrawal]
Value -> Parser AccountWithdrawal
(Value -> Parser AccountWithdrawal)
-> (Value -> Parser [AccountWithdrawal])
-> FromJSON AccountWithdrawal
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AccountWithdrawal]
$cparseJSONList :: Value -> Parser [AccountWithdrawal]
parseJSON :: Value -> Parser AccountWithdrawal
$cparseJSON :: Value -> Parser AccountWithdrawal
FromJSON, [AccountWithdrawal] -> Encoding
[AccountWithdrawal] -> Value
AccountWithdrawal -> Encoding
AccountWithdrawal -> Value
(AccountWithdrawal -> Value)
-> (AccountWithdrawal -> Encoding)
-> ([AccountWithdrawal] -> Value)
-> ([AccountWithdrawal] -> Encoding)
-> ToJSON AccountWithdrawal
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AccountWithdrawal] -> Encoding
$ctoEncodingList :: [AccountWithdrawal] -> Encoding
toJSONList :: [AccountWithdrawal] -> Value
$ctoJSONList :: [AccountWithdrawal] -> Value
toEncoding :: AccountWithdrawal -> Encoding
$ctoEncoding :: AccountWithdrawal -> Encoding
toJSON :: AccountWithdrawal -> Value
$ctoJSON :: AccountWithdrawal -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountWithdrawal", CamelToSnake]] AccountWithdrawal

instance ToSample AccountWithdrawal where
  toSamples :: Proxy AccountWithdrawal -> [(Text, AccountWithdrawal)]
toSamples = [(Text, AccountWithdrawal)]
-> Proxy AccountWithdrawal -> [(Text, AccountWithdrawal)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountWithdrawal)]
 -> Proxy AccountWithdrawal -> [(Text, AccountWithdrawal)])
-> [(Text, AccountWithdrawal)]
-> Proxy AccountWithdrawal
-> [(Text, AccountWithdrawal)]
forall a b. (a -> b) -> a -> b
$ [AccountWithdrawal] -> [(Text, AccountWithdrawal)]
forall a. [a] -> [(Text, a)]
samples
    [ AccountWithdrawal :: Lovelaces -> TxHash -> AccountWithdrawal
AccountWithdrawal
        { _accountWithdrawalAmount :: Lovelaces
_accountWithdrawalAmount = Lovelaces
454541212442
        , _accountWithdrawalTxHash :: TxHash
_accountWithdrawalTxHash = TxHash
"48a9625c841eea0dd2bb6cf551eabe6523b7290c9ce34be74eedef2dd8f7ecc5"
        }
    , AccountWithdrawal :: Lovelaces -> TxHash -> AccountWithdrawal
AccountWithdrawal
        { _accountWithdrawalAmount :: Lovelaces
_accountWithdrawalAmount = Lovelaces
97846969
        , _accountWithdrawalTxHash :: TxHash
_accountWithdrawalTxHash = TxHash
"4230b0cbccf6f449f0847d8ad1d634a7a49df60d8c142bb8cc2dbc8ca03d9e34"
        }
    ]

-- | Account MIR (Move Instantaneous Reward)
data AccountMir = AccountMir
  { AccountMir -> Lovelaces
_accountMirAmount :: Lovelaces -- ^ MIR amount in Lovelaces
  , AccountMir -> TxHash
_accountMirTxHash :: TxHash -- ^ Hash of the transaction containing the MIR
  }
  deriving stock (Int -> AccountMir -> ShowS
[AccountMir] -> ShowS
AccountMir -> String
(Int -> AccountMir -> ShowS)
-> (AccountMir -> String)
-> ([AccountMir] -> ShowS)
-> Show AccountMir
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountMir] -> ShowS
$cshowList :: [AccountMir] -> ShowS
show :: AccountMir -> String
$cshow :: AccountMir -> String
showsPrec :: Int -> AccountMir -> ShowS
$cshowsPrec :: Int -> AccountMir -> ShowS
Show, AccountMir -> AccountMir -> Bool
(AccountMir -> AccountMir -> Bool)
-> (AccountMir -> AccountMir -> Bool) -> Eq AccountMir
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountMir -> AccountMir -> Bool
$c/= :: AccountMir -> AccountMir -> Bool
== :: AccountMir -> AccountMir -> Bool
$c== :: AccountMir -> AccountMir -> Bool
Eq, (forall x. AccountMir -> Rep AccountMir x)
-> (forall x. Rep AccountMir x -> AccountMir) -> Generic AccountMir
forall x. Rep AccountMir x -> AccountMir
forall x. AccountMir -> Rep AccountMir x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountMir x -> AccountMir
$cfrom :: forall x. AccountMir -> Rep AccountMir x
Generic)
  deriving (Value -> Parser [AccountMir]
Value -> Parser AccountMir
(Value -> Parser AccountMir)
-> (Value -> Parser [AccountMir]) -> FromJSON AccountMir
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AccountMir]
$cparseJSONList :: Value -> Parser [AccountMir]
parseJSON :: Value -> Parser AccountMir
$cparseJSON :: Value -> Parser AccountMir
FromJSON, [AccountMir] -> Encoding
[AccountMir] -> Value
AccountMir -> Encoding
AccountMir -> Value
(AccountMir -> Value)
-> (AccountMir -> Encoding)
-> ([AccountMir] -> Value)
-> ([AccountMir] -> Encoding)
-> ToJSON AccountMir
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AccountMir] -> Encoding
$ctoEncodingList :: [AccountMir] -> Encoding
toJSONList :: [AccountMir] -> Value
$ctoJSONList :: [AccountMir] -> Value
toEncoding :: AccountMir -> Encoding
$ctoEncoding :: AccountMir -> Encoding
toJSON :: AccountMir -> Value
$ctoJSON :: AccountMir -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountMir", CamelToSnake]] AccountMir

instance ToSample AccountMir where
  toSamples :: Proxy AccountMir -> [(Text, AccountMir)]
toSamples = [(Text, AccountMir)] -> Proxy AccountMir -> [(Text, AccountMir)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountMir)] -> Proxy AccountMir -> [(Text, AccountMir)])
-> [(Text, AccountMir)] -> Proxy AccountMir -> [(Text, AccountMir)]
forall a b. (a -> b) -> a -> b
$ [AccountMir] -> [(Text, AccountMir)]
forall a. [a] -> [(Text, a)]
samples
    [ AccountMir :: Lovelaces -> TxHash -> AccountMir
AccountMir
        { _accountMirAmount :: Lovelaces
_accountMirAmount = Lovelaces
6202170
        , _accountMirTxHash :: TxHash
_accountMirTxHash = TxHash
"2dd15e0ef6e6a17841cb9541c27724072ce4d4b79b91e58432fbaa32d9572531"
        }
    , AccountMir :: Lovelaces -> TxHash -> AccountMir
AccountMir
        { _accountMirAmount :: Lovelaces
_accountMirAmount = Lovelaces
1202170
        , _accountMirTxHash :: TxHash
_accountMirTxHash = TxHash
"1dd15e0ef6e6a17841cb9541c27724072ce4d4b79b91e58432fbaa32d9572531"
        }
    ]

-- | Address associated with an account address
newtype AddressAssociated = AddressAssociated {AddressAssociated -> Address
_addressAssociatedAddress :: Address}
  deriving stock (AddressAssociated -> AddressAssociated -> Bool
(AddressAssociated -> AddressAssociated -> Bool)
-> (AddressAssociated -> AddressAssociated -> Bool)
-> Eq AddressAssociated
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddressAssociated -> AddressAssociated -> Bool
$c/= :: AddressAssociated -> AddressAssociated -> Bool
== :: AddressAssociated -> AddressAssociated -> Bool
$c== :: AddressAssociated -> AddressAssociated -> Bool
Eq, Int -> AddressAssociated -> ShowS
[AddressAssociated] -> ShowS
AddressAssociated -> String
(Int -> AddressAssociated -> ShowS)
-> (AddressAssociated -> String)
-> ([AddressAssociated] -> ShowS)
-> Show AddressAssociated
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddressAssociated] -> ShowS
$cshowList :: [AddressAssociated] -> ShowS
show :: AddressAssociated -> String
$cshow :: AddressAssociated -> String
showsPrec :: Int -> AddressAssociated -> ShowS
$cshowsPrec :: Int -> AddressAssociated -> ShowS
Show, (forall x. AddressAssociated -> Rep AddressAssociated x)
-> (forall x. Rep AddressAssociated x -> AddressAssociated)
-> Generic AddressAssociated
forall x. Rep AddressAssociated x -> AddressAssociated
forall x. AddressAssociated -> Rep AddressAssociated x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddressAssociated x -> AddressAssociated
$cfrom :: forall x. AddressAssociated -> Rep AddressAssociated x
Generic)
  deriving (Value -> Parser [AddressAssociated]
Value -> Parser AddressAssociated
(Value -> Parser AddressAssociated)
-> (Value -> Parser [AddressAssociated])
-> FromJSON AddressAssociated
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AddressAssociated]
$cparseJSONList :: Value -> Parser [AddressAssociated]
parseJSON :: Value -> Parser AddressAssociated
$cparseJSON :: Value -> Parser AddressAssociated
FromJSON, [AddressAssociated] -> Encoding
[AddressAssociated] -> Value
AddressAssociated -> Encoding
AddressAssociated -> Value
(AddressAssociated -> Value)
-> (AddressAssociated -> Encoding)
-> ([AddressAssociated] -> Value)
-> ([AddressAssociated] -> Encoding)
-> ToJSON AddressAssociated
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AddressAssociated] -> Encoding
$ctoEncodingList :: [AddressAssociated] -> Encoding
toJSONList :: [AddressAssociated] -> Value
$ctoJSONList :: [AddressAssociated] -> Value
toEncoding :: AddressAssociated -> Encoding
$ctoEncoding :: AddressAssociated -> Encoding
toJSON :: AddressAssociated -> Value
$ctoJSON :: AddressAssociated -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_addressAssociated", CamelToSnake]] AddressAssociated

instance ToSample AddressAssociated where
  toSamples :: Proxy AddressAssociated -> [(Text, AddressAssociated)]
toSamples = [(Text, AddressAssociated)]
-> Proxy AddressAssociated -> [(Text, AddressAssociated)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AddressAssociated)]
 -> Proxy AddressAssociated -> [(Text, AddressAssociated)])
-> [(Text, AddressAssociated)]
-> Proxy AddressAssociated
-> [(Text, AddressAssociated)]
forall a b. (a -> b) -> a -> b
$ [AddressAssociated] -> [(Text, AddressAssociated)]
forall a. [a] -> [(Text, a)]
samples
    [ Address -> AddressAssociated
AddressAssociated Address
"addr1qx2kd28nq8ac5prwg32hhvudlwggpgfp8utlyqxu6wqgz62f79qsdmm5dsknt9ecr5w468r9ey0fxwkdrwh08ly3tu9sy0f4qd"
    , Address -> AddressAssociated
AddressAssociated Address
"addr1q8j55h253zcvl326sk5qdt2n8z7eghzspe0ekxgncr796s2f79qsdmm5dsknt9ecr5w468r9ey0fxwkdrwh08ly3tu9sjmd35m"
    ]